-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Hey! Hey! Can u rel8? -- -- Hey! Hey! Can u rel8? @package rel8 @version 1.0.0.1 module Rel8.Expr.Time -- | Corresponds to date(now()). today :: Expr Day -- | Corresponds to calling the date function with a given time. toDay :: Expr UTCTime -> Expr Day -- | Corresponds to x::timestamptz. fromDay :: Expr Day -> Expr UTCTime -- | Move forward a given number of days from a particular day. addDays :: Expr Int32 -> Expr Day -> Expr Day -- | Find the number of days between two days. Corresponds to the -- - operator. diffDays :: Expr Day -> Expr Day -> Expr Int32 -- | Subtract a given number of days from a particular Day. subtractDays :: Expr Int32 -> Expr Day -> Expr Day -- | Corresponds to now(). now :: Expr UTCTime -- | Add a time interval to a point in time, yielding a new point in time. addTime :: Expr CalendarDiffTime -> Expr UTCTime -> Expr UTCTime -- | Find the duration between two times. diffTime :: Expr UTCTime -> Expr UTCTime -> Expr CalendarDiffTime -- | Subtract a time interval from a point in time, yielding a new point in -- time. subtractTime :: Expr CalendarDiffTime -> Expr UTCTime -> Expr UTCTime scaleInterval :: Expr Double -> Expr CalendarDiffTime -> Expr CalendarDiffTime -- | An interval of one second. second :: Expr CalendarDiffTime -- | Create a literal interval from a number of seconds. seconds :: Expr Double -> Expr CalendarDiffTime -- | An interval of one minute. minute :: Expr CalendarDiffTime -- | Create a literal interval from a number of minutes. minutes :: Expr Double -> Expr CalendarDiffTime -- | An interval of one hour. hour :: Expr CalendarDiffTime -- | Create a literal interval from a number of hours. hours :: Expr Double -> Expr CalendarDiffTime -- | An interval of one day. day :: Expr CalendarDiffTime -- | Create a literal interval from a number of days. days :: Expr Double -> Expr CalendarDiffTime -- | An interval of one week. week :: Expr CalendarDiffTime -- | Create a literal interval from a number of weeks. weeks :: Expr Double -> Expr CalendarDiffTime -- | An interval of one month. month :: Expr CalendarDiffTime -- | Create a literal interval from a number of months. months :: Expr Double -> Expr CalendarDiffTime -- | An interval of one year. year :: Expr CalendarDiffTime -- | Create a literal interval from a number of years. years :: Expr Double -> Expr CalendarDiffTime module Rel8.Expr.Text -- | The PostgreSQL string concatenation operator. (++.) :: Expr Text -> Expr Text -> Expr Text infixr 6 ++. -- | Matches regular expression, case sensitive -- -- Corresponds to the ~. operator. (~.) :: Expr Text -> Expr Text -> Expr Bool infix 2 ~. -- | Matches regular expression, case insensitive -- -- Corresponds to the ~* operator. (~*) :: Expr Text -> Expr Text -> Expr Bool infix 2 ~* -- | Does not match regular expression, case sensitive -- -- Corresponds to the !~ operator. (!~) :: Expr Text -> Expr Text -> Expr Bool infix 2 !~ -- | Does not match regular expression, case insensitive -- -- Corresponds to the !~* operator. (!~*) :: Expr Text -> Expr Text -> Expr Bool infix 2 !~* -- | Corresponds to the bit_length function. bitLength :: Expr Text -> Expr Int32 -- | Corresponds to the char_length function. charLength :: Expr Text -> Expr Int32 -- | Corresponds to the lower function. lower :: Expr Text -> Expr Text -- | Corresponds to the octet_length function. octetLength :: Expr Text -> Expr Int32 -- | Corresponds to the upper function. upper :: Expr Text -> Expr Text -- | Corresponds to the ascii function. ascii :: Expr Text -> Expr Int32 -- | Corresponds to the btrim function. btrim :: Expr Text -> Maybe (Expr Text) -> Expr Text -- | Corresponds to the chr function. chr :: Expr Int32 -> Expr Text -- | Corresponds to the convert function. convert :: Expr ByteString -> Expr Text -> Expr Text -> Expr ByteString -- | Corresponds to the convert_from function. convertFrom :: Expr ByteString -> Expr Text -> Expr Text -- | Corresponds to the convert_to function. convertTo :: Expr Text -> Expr Text -> Expr ByteString -- | Corresponds to the decode function. decode :: Expr Text -> Expr Text -> Expr ByteString -- | Corresponds to the encode function. encode :: Expr ByteString -> Expr Text -> Expr Text -- | Corresponds to the initcap function. initcap :: Expr Text -> Expr Text -- | Corresponds to the left function. left :: Expr Text -> Expr Int32 -> Expr Text -- | Corresponds to the length function. length :: Expr Text -> Expr Int32 -- | Corresponds to the length function. lengthEncoding :: Expr ByteString -> Expr Text -> Expr Int32 -- | Corresponds to the lpad function. lpad :: Expr Text -> Expr Int32 -> Maybe (Expr Text) -> Expr Text -- | Corresponds to the ltrim function. ltrim :: Expr Text -> Maybe (Expr Text) -> Expr Text -- | Corresponds to the md5 function. md5 :: Expr Text -> Expr Text -- | Corresponds to the pg_client_encoding() expression. pgClientEncoding :: Expr Text -- | Corresponds to the quote_ident function. quoteIdent :: Expr Text -> Expr Text -- | Corresponds to the quote_literal function. quoteLiteral :: Expr Text -> Expr Text -- | Corresponds to the quote_nullable function. quoteNullable :: Expr Text -> Expr Text -- | Corresponds to the regexp_replace function. regexpReplace :: () => Expr Text -> Expr Text -> Expr Text -> Maybe (Expr Text) -> Expr Text -- | Corresponds to the regexp_split_to_array function. regexpSplitToArray :: () => Expr Text -> Expr Text -> Maybe (Expr Text) -> Expr [Text] -- | Corresponds to the repeat function. repeat :: Expr Text -> Expr Int32 -> Expr Text -- | Corresponds to the replace function. replace :: Expr Text -> Expr Text -> Expr Text -> Expr Text -- | Corresponds to the reverse function. reverse :: Expr Text -> Expr Text -- | Corresponds to the right function. right :: Expr Text -> Expr Int32 -> Expr Text -- | Corresponds to the rpad function. rpad :: Expr Text -> Expr Int32 -> Maybe (Expr Text) -> Expr Text -- | Corresponds to the rtrim function. rtrim :: Expr Text -> Maybe (Expr Text) -> Expr Text -- | Corresponds to the split_part function. splitPart :: Expr Text -> Expr Text -> Expr Int32 -> Expr Text -- | Corresponds to the strpos function. strpos :: Expr Text -> Expr Text -> Expr Int32 -- | Corresponds to the substr function. substr :: Expr Text -> Expr Int32 -> Maybe (Expr Int32) -> Expr Text -- | Corresponds to the translate function. translate :: Expr Text -> Expr Text -> Expr Text -> Expr Text module Rel8.Expr.Num -- | Cast DBIntegral types to DBNum types. For example, this -- can be useful if you need to turn an Expr Int32 into an -- Expr Double. fromIntegral :: (Sql DBIntegral a, Sql DBNum b, Homonullable a b) => Expr a -> Expr b -- | Cast DBNum types to DBFractional types. For example, his -- can be useful to convert Expr Float to Expr Double. realToFrac :: (Sql DBNum a, Sql DBFractional b, Homonullable a b) => Expr a -> Expr b -- | Perform integral division. Corresponds to the div() function. div :: Sql DBIntegral a => Expr a -> Expr a -> Expr a -- | Corresponds to the mod() function. mod :: Sql DBIntegral a => Expr a -> Expr a -> Expr a -- | Round a DBFractional to a DBIntegral by rounding to the -- nearest larger integer. -- -- Corresponds to the ceiling() function. ceiling :: (Sql DBFractional a, Sql DBIntegral b, Homonullable a b) => Expr a -> Expr b -- | Round a DFractional to a DBIntegral by rounding to the -- nearest smaller integer. -- -- Corresponds to the floor() function. floor :: (Sql DBFractional a, Sql DBIntegral b, Homonullable a b) => Expr a -> Expr b -- | Round a DBFractional to a DBIntegral by rounding to the -- nearest integer. -- -- Corresponds to the round() function. round :: (Sql DBFractional a, Sql DBIntegral b, Homonullable a b) => Expr a -> Expr b -- | Round a DBFractional to a DBIntegral by rounding to the -- nearest integer towards zero. truncate :: (Sql DBFractional a, Sql DBIntegral b, Homonullable a b) => Expr a -> Expr b module Rel8 -- | Haskell types that can be represented as expressions in a database. -- There should be an instance of DBType 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. class NotNull a => DBType a typeInformation :: DBType a => TypeInformation a -- | A deriving-via helper type for column types that store a Haskell value -- using a JSON encoding described by aeson's ToJSON and -- FromJSON type classes. newtype JSONEncoded a JSONEncoded :: a -> JSONEncoded a [fromJSONEncoded] :: JSONEncoded a -> a -- | Like JSONEncoded, but works for jsonb columns. newtype JSONBEncoded a JSONBEncoded :: a -> JSONBEncoded a [fromJSONBEncoded] :: JSONBEncoded a -> a -- | A deriving-via helper type for column types that store a Haskell value -- using a Haskell's Read and Show type classes. newtype ReadShow a ReadShow :: a -> ReadShow a [fromReadShow] :: ReadShow a -> a -- | A 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 DBComposite to -- specify the name of this Postgres type and the names of the individual -- fields (for projecting with decompose). newtype Composite a Composite :: a -> Composite a -- | DBComposite is used to associate composite type metadata with a -- Haskell type. class (DBType a, HKDable a) => DBComposite a -- | The names of all fields in the composite type that a maps to. compositeFields :: DBComposite a => HKD a Name -- | The name of the composite type that a maps to. compositeTypeName :: DBComposite a => String -- | Collapse a HKD into a PostgreSQL composite type. -- -- HKD values are represented in queries by having a column for -- each field in the corresponding Haskell type. compose collapses -- these columns into a single column expression, by combining them into -- a PostgreSQL composite type. compose :: DBComposite a => HKD a Expr -> Expr a -- | Expand a composite type into a HKD. -- -- decompose is the inverse of compose. decompose :: forall a. DBComposite a => Expr a -> HKD a Expr -- | A 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 -- DBEnum 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). newtype Enum a Enum :: a -> Enum a -- | DBEnum contains the necessary metadata to describe a -- PostgreSQL enum type. class (DBType a, Enumable a) => DBEnum a -- | Map 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. enumValue :: DBEnum a => a -> String -- | The name of the PostgreSQL enum type that a maps to. enumTypeName :: DBEnum a => String -- | Types that are sum types, where each constructor is unary (that is, -- has no fields). class (Generic a, GEnumable (Rep a)) => Enumable a -- | TypeInformation 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. data TypeInformation a TypeInformation :: (a -> PrimExpr) -> Value a -> String -> TypeInformation a -- | How to encode a single Haskell value as a SQL expression. [encode] :: TypeInformation a -> a -> PrimExpr -- | How to deserialize a single result back to Haskell. [decode] :: TypeInformation a -> Value a -- | The name of the SQL type. [typeName] :: TypeInformation a -> String -- | Simultaneously 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 DBType. -- -- The mapping is required to be total. If you have a partial mapping, -- see parseTypeInformation. mapTypeInformation :: () => (a -> b) -> (b -> a) -> TypeInformation a -> TypeInformation b -- | Apply a parser to TypeInformation. -- -- This can be used if the data stored in the database should only be -- subset of a given TypeInformation. The parser is applied when -- deserializing rows returned - the encoder assumes that the input data -- is already in the appropriate form. parseTypeInformation :: () => (a -> Either String b) -> (b -> a) -> TypeInformation a -> TypeInformation b -- | The class of DBTypes that form a semigroup. This class is -- purely a Rel8 concept, and exists to mirror the Semigroup -- class. class DBType a => DBSemigroup a -- | An associative operation. (<>.) :: DBSemigroup a => Expr a -> Expr a -> Expr a infixr 6 <>. -- | The class of DBTypes that form a semigroup. This class is -- purely a Rel8 concept, and exists to mirror the Monoid class. class DBSemigroup a => DBMonoid a memptyExpr :: DBMonoid a => Expr a -- | The class of database types that support the +, *, -- - operators, and the abs, negate, -- sign functions. class DBType a => DBNum a -- | The class of database types that can be coerced to from integral -- expressions. This is a Rel8 concept, and allows us to provide -- fromIntegral. class DBNum a => DBIntegral a -- | The class of database types that support the / operator. class DBNum a => DBFractional a -- | The class of database types that support the / operator. class DBFractional a => DBFloating a -- | This type class allows you to define custom Tables 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: -- -- -- --
--   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. -- -- -- -- This type class should be derived generically for all table types in -- your project. To do this, enable the DeriveAnyType and -- DeriveGeneric language extensions: -- --
--   {-# LANGUAGE DeriveAnyClass, DeriveGeneric #-}
--   
--   data MyType f = MyType { fieldA :: Column f T }
--     deriving ( GHC.Generics.Generic, Rel8able )
--   
class HTable (GColumns t) => Rel8able t -- | The kind of Rel8able types type KRel8able = Rel8able -- | 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. type family Column context a type family HADT context t -- | Nest an Either value within a Rel8able. HEither f -- a b will produce a EitherTable a b in the -- Expr context, and a Either a b in the -- Result context. type family HEither context -- | Nest a Maybe value within a Rel8able. HMaybe f -- a will produce a MaybeTable a in the Expr -- context, and a Maybe a in the Result context. type family HMaybe context -- | Nest a list within a Rel8able. HList f a will -- produce a ListTable a in the Expr context, and -- a [a] in the Result context. type family HList context -- | Nest a NonEmpty list within a Rel8able. HNonEmpty -- f a will produce a NonEmptyTable a in the -- Expr context, and a NonEmpty a in the -- Result context. type family HNonEmpty context -- | Nest an These value within a Rel8able. HThese f a -- b will produce a TheseTable a b in the -- Expr context, and a These a b in the -- Result context. type family HThese context type family Lift context a -- | Tables 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 -- Expr context), aggregations (the Aggregate context), -- insert values (the Insert contex), among others. -- -- In typical usage of Rel8 you don't need to derive instances of -- Table yourself, as anything that's an instance of -- Rel8able is always a Table. class (HTable (Columns a), context ~ Context a) => Table context a | a -> context where { -- | The HTable functor that describes the schema of this table. type family Columns a :: HTable; -- | The common context that all columns use as an interpretation. type family Context a :: Context; type family Unreify a :: Type; type Columns a = Eval (GGColumns (GAlgebra (Rep (Record a))) TColumns (Rep (Record a))); type Context a = Eval (GGContext (GAlgebra (Rep (Record a))) TContext (Rep (Record a))); type Unreify a = DefaultUnreify a; } toColumns :: Table context a => a -> Columns a (Col context) fromColumns :: Table context a => Columns a (Col context) -> a reify :: Table context a => (context :~: Reify ctx) -> Unreify a -> a unreify :: Table context a => (context :~: Reify ctx) -> a -> Unreify a toColumns :: (Table context a, Generic (Record a), KnownAlgebra (GAlgebra (Rep (Record a))), Eval (GGTable (GAlgebra (Rep (Record a))) (TTable context) TColumns (Col context) (Rep (Record a))), Columns a ~ Eval (GGColumns (GAlgebra (Rep (Record a))) TColumns (Rep (Record a))), Context a ~ Eval (GGContext (GAlgebra (Rep (Record a))) TContext (Rep (Record a)))) => a -> Columns a (Col context) fromColumns :: (Table context a, Generic (Record a), KnownAlgebra (GAlgebra (Rep (Record a))), Eval (GGTable (GAlgebra (Rep (Record a))) (TTable context) TColumns (Col context) (Rep (Record a))), Columns a ~ Eval (GGColumns (GAlgebra (Rep (Record a))) TColumns (Rep (Record a))), Context a ~ Eval (GGContext (GAlgebra (Rep (Record a))) TContext (Rep (Record a)))) => Columns a (Col context) -> a reify :: (Table context a, Generic (Record a), Generic (Record (Unreify a)), GMappable (TTable context) (Rep (Record a)), Rep (Record (Unreify a)) ~ GMap TUnreify (Rep (Record a))) => (context :~: Reify ctx) -> Unreify a -> a unreify :: (Table context a, Generic (Record a), Generic (Record (Unreify a)), GMappable (TTable context) (Rep (Record a)), Rep (Record (Unreify a)) ~ GMap TUnreify (Rep (Record a))) => (context :~: Reify ctx) -> a -> Unreify a -- | A HTable is a functor-indexed/higher-kinded data type that is -- representable (htabulate/hfield), constrainable -- (hdicts), and specified (hspecs). -- -- This is an internal concept for Rel8, and you should not need to -- define instances yourself or specify this constraint. class HTable t -- | Recontextualize from to a b is evidence that the types -- a and b are related, and that b is the same -- type as a, but after changing the context from the initial -- context from, to the new context to. class (Table from a, Table to b, Congruent a b, Recontextualize from from a a, Recontextualize to to b b, Recontextualize to from b a) => Recontextualize from to a b | a -> from, b -> to, a to -> b, b from -> a -- | Like Alt in Haskell. This class is purely a Rel8 concept, and -- allows you to take a choice between two tables. See also -- AlternativeTable. -- -- For example, using <|>: on MaybeTable allows you -- to combine two tables and to return the first one that is a "just" -- MaybeTable. class AltTable f -- | An associative binary operation on Tables. (<|>:) :: (AltTable f, Table Expr a) => f a -> f a -> f a infixl 3 <|>: -- | Like Alternative in Haskell, some Tables form a monoid -- on applicative functors. class AltTable f => AlternativeTable f -- | The identity of <|>:. emptyTable :: (AlternativeTable f, Table Expr a) => f a -- | The class of Tables 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 Table have an instance of -- DBEq". class Table Expr a => EqTable a -- | Compare two Tables for equality. This corresponds to comparing -- all columns inside each table for equality, and combining all -- comparisons with AND. (==:) :: forall a. EqTable a => a -> a -> Expr Bool infix 4 ==: -- | Test if two Tables are different. This corresponds to comparing -- all columns inside each table for inequality, and combining all -- comparisons with OR. (/=:) :: forall a. EqTable a => a -> a -> Expr Bool infix 4 /=: -- | 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 -- DBOrd". class EqTable a => OrdTable a -- | Construct an Order for a Table by sorting all columns -- into ascending orders (any nullable columns will be sorted with -- NULLS FIRST). ascTable :: forall a. OrdTable a => Order a -- | Construct an Order for a Table by sorting all columns -- into descending orders (any nullable columns will be sorted with -- NULLS LAST). descTable :: forall a. OrdTable a => Order a -- | Use lit to turn literal Haskell values into expressions. -- lit is capable of lifting single Exprs to full -- tables. lit :: forall exprs a. Serializable exprs a => a -> exprs -- | An if-then-else expression on tables. -- -- bool x y p returns x if p is -- False, and returns y if p is True. bool :: Table Expr a => a -> a -> Expr Bool -> a -- | Produce 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. case_ :: Table Expr a => [(Expr Bool, a)] -> a -> a -- | 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 Nothing, 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. data MaybeTable a -- | Perform case analysis on a MaybeTable. Like maybe. maybeTable :: Table Expr b => b -> (a -> b) -> MaybeTable a -> b -- | Project a single expression out of a MaybeTable. You can think -- of this operator like the $ operator, but it also has the -- ability to return null. ($?) :: forall a b. Sql DBType b => (a -> Expr b) -> MaybeTable a -> Expr (Nullify b) infixl 4 $? -- | The null table. Like Nothing. nothingTable :: Table Expr a => MaybeTable a -- | Lift any table into MaybeTable. Like Just. Note you can -- also use pure. justTable :: a -> MaybeTable a -- | Check if a MaybeTable is absent of any row. Like -- isNothing. isNothingTable :: MaybeTable a -> Expr Bool -- | Check if a MaybeTable contains a row. Like isJust. isJustTable :: MaybeTable a -> Expr Bool -- | Convert a query that might return zero rows to a query that always -- returns at least one row. -- -- To speak in more concrete terms, optional is most useful to -- write LEFT JOINs. optional :: Query a -> Query (MaybeTable a) -- | Filter out MaybeTables, returning only the tables that are -- not-null. -- -- This operation can be used to "undo" the effect of optional, -- which operationally is like turning a LEFT JOIN back into a -- full JOIN. You can think of this as analogous to -- catMaybes. catMaybeTable :: MaybeTable a -> Query a -- | Extend 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. traverseMaybeTable :: (a -> Query b) -> MaybeTable a -> Query (MaybeTable b) -- | Construct a MaybeTable in the Name context. This can be -- useful if you have a MaybeTable that you are storing in a table -- and need to construct a TableSchema. nameMaybeTable :: Name (Maybe MaybeTag) -> a -> MaybeTable a -- | An EitherTable a b is a Rel8 table that contains either the -- table a or the table b. You can construct an -- EitherTable using leftTable and rightTable, and -- eliminate/pattern match using eitherTable. -- -- An EitherTable is operationally the same as Haskell's -- Either type, but adapted to work with Rel8. data EitherTable a b -- | Pattern match/eliminate an EitherTable, by providing mappings -- from a leftTable and rightTable. eitherTable :: Table Expr c => (a -> c) -> (b -> c) -> EitherTable a b -> c -- | Construct a left EitherTable. Like Left. leftTable :: Table Expr b => a -> EitherTable a b -- | Construct a right EitherTable. Like Right. rightTable :: Table Expr a => b -> EitherTable a b -- | Test if an EitherTable is a leftTable. isLeftTable :: EitherTable a b -> Expr Bool -- | Test if an EitherTable is a rightTable. isRightTable :: EitherTable a b -> Expr Bool -- | Filter EitherTables, keeping only leftTables. keepLeftTable :: EitherTable a b -> Query a -- | Filter EitherTables, keeping only rightTables. keepRightTable :: EitherTable a b -> Query b -- | bitraverseEitherTable f g x will pass all leftTables -- through f and all rightTables through g. -- The results are then lifted back into leftTable and -- rightTable, respectively. This is similar to -- bitraverse for Either. -- -- 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
--   ]
--   
bitraverseEitherTable :: () => (a -> Query c) -> (b -> Query d) -> EitherTable a b -> Query (EitherTable c d) -- | Construct a EitherTable in the Name context. This can be -- useful if you have a EitherTable that you are storing in a -- table and need to construct a TableSchema. nameEitherTable :: Name EitherTag -> a -> b -> EitherTable a b -- | TheseTable a b is a Rel8 table that contains either the table -- a, the table b, or both tables a and -- b. You can construct TheseTables using -- thisTable, thatTable and thoseTable. -- TheseTables can be eliminated/pattern matched using -- theseTable. -- -- TheseTable is operationally the same as Haskell's -- These type, but adapted to work with Rel8. data TheseTable a b -- | Pattern match on a TheseTable. Corresponds to these. theseTable :: Table Expr c => (a -> c) -> (b -> c) -> (a -> b -> c) -> TheseTable a b -> c -- | Construct a TheseTable. Corresponds to This. thisTable :: Table Expr b => a -> TheseTable a b -- | Construct a TheseTable. Corresponds to That. thatTable :: Table Expr a => b -> TheseTable a b -- | Construct a TheseTable. Corresponds to These. thoseTable :: a -> b -> TheseTable a b -- | Test if a TheseTable was constructed with thisTable. -- -- Corresponds to isThis. isThisTable :: TheseTable a b -> Expr Bool -- | Test if a TheseTable was constructed with thatTable. -- -- Corresponds to isThat. isThatTable :: TheseTable a b -> Expr Bool -- | Test if a TheseTable was constructed with thoseTable. -- -- Corresponds to isThese. isThoseTable :: TheseTable a b -> Expr Bool -- | Test if the a side of TheseTable a b is present. -- -- Corresponds to hasHere. hasHereTable :: TheseTable a b -> Expr Bool -- | Test if the b table of TheseTable a b is present. -- -- Corresponds to hasThere. hasThereTable :: TheseTable a b -> Expr Bool -- | Attempt to project out the a table of a TheseTable a -- b. -- -- Corresponds to justHere. justHereTable :: TheseTable a b -> MaybeTable a -- | Attempt to project out the b table of a TheseTable a -- b. -- -- Corresponds to justThere. justThereTable :: TheseTable a b -> MaybeTable b -- | Corresponds to a FULL OUTER JOIN between two queries. alignBy :: (Table Expr a, Table Expr b) => (a -> b -> Expr Bool) -> Query a -> Query b -> Query (TheseTable a b) -- | Filter TheseTables, keeping only thisTables and -- thoseTables. keepHereTable :: TheseTable a b -> Query (a, MaybeTable b) -- | Filter TheseTables, keeping on loseHereTable :: TheseTable a b -> Query b keepThereTable :: TheseTable a b -> Query (MaybeTable a, b) loseThereTable :: TheseTable a b -> Query a keepThisTable :: TheseTable a b -> Query a loseThisTable :: TheseTable a b -> Query (MaybeTable a, b) keepThatTable :: TheseTable a b -> Query b loseThatTable :: TheseTable a b -> Query (a, MaybeTable b) keepThoseTable :: TheseTable a b -> Query (a, b) loseThoseTable :: TheseTable a b -> Query (EitherTable a b) bitraverseTheseTable :: () => (a -> Query c) -> (b -> Query d) -> TheseTable a b -> Query (TheseTable c d) -- | Construct a TheseTable in the Name context. This can be -- useful if you have a TheseTable that you are storing in a table -- and need to construct a TableSchema. nameTheseTable :: () => Name (Maybe MaybeTag) -> Name (Maybe MaybeTag) -> a -> b -> TheseTable a b -- | A ListTable value contains zero or more instances of -- a. You construct ListTables with many or -- listAgg. data ListTable a -- | Construct a ListTable from a list of expressions. listTable :: Table Expr a => [a] -> ListTable a -- | Construct a ListTable in the Name context. This can be -- useful if you have a ListTable that you are storing in a table -- and need to construct a TableSchema. nameListTable :: Table Name a => a -> ListTable a -- | Aggregate a Query into a ListTable. If the supplied -- query returns 0 rows, this function will produce a Query 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 many from -- Control.Applicative. many :: Table Expr a => Query a -> Query (ListTable a) -- | A version of many specialised to single expressions. manyExpr :: Sql DBType a => Query (Expr a) -> Query (Expr [a]) -- | Expand a ListTable into a Query, where each row in the -- query is an element of the given ListTable. -- -- catListTable is an inverse to many. catListTable :: Table Expr a => ListTable a -> Query a -- | Expand an expression that contains a list into a Query, where -- each row in the query is an element of the given list. -- -- catList is an inverse to manyExpr. catList :: Sql DBType a => Expr [a] -> Query (Expr a) -- | A NonEmptyTable value contains one or more instances of -- a. You construct NonEmptyTables with some or -- nonEmptyAgg. data NonEmptyTable a -- | Construct a NonEmptyTable from a non-empty list of -- expressions. nonEmptyTable :: Table Expr a => NonEmpty a -> NonEmptyTable a -- | Construct a NonEmptyTable in the Name context. This can -- be useful if you have a NonEmptyTable that you are storing in a -- table and need to construct a TableSchema. nameNonEmptyTable :: Table Name a => a -> NonEmptyTable a -- | Aggregate a Query into a NonEmptyTable. If the supplied -- query returns 0 rows, this function will produce a Query 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 some from -- Control.Applicative. some :: Table Expr a => Query a -> Query (NonEmptyTable a) -- | A version of many specialised to single expressions. someExpr :: Sql DBType a => Query (Expr a) -> Query (Expr (NonEmpty a)) -- | Expand a NonEmptyTable into a Query, where each row in -- the query is an element of the given NonEmptyTable. -- -- catNonEmptyTable is an inverse to some. catNonEmptyTable :: Table Expr a => NonEmptyTable a -> Query a -- | Expand an expression that contains a non-empty list into a -- Query, where each row in the query is an element of the given -- list. -- -- catNonEmpty is an inverse to someExpr. catNonEmpty :: Sql DBType a => Expr (NonEmpty a) -> Query (Expr a) data ADT t context class (Generic (t Result), HTable (GColumnsADT t), GTableADT (TTable (Reify Result)) TColumns (Col (Reify Result)) (GRecord (Rep (t (Reify Result)))), GRecordable (Rep (t (Reify Result))), GMappable (TTable (Reify Result)) (Rep (t (Reify Result))), GMap TUnreify (Rep (t (Reify Result))) ~ Rep (t Result)) => ADTable t type BuildADT t name = GGBuild 'Sum name (ADTRep t) (ADT t Expr) buildADT :: forall t name. BuildableADT t name => BuildADT t name type ConstructADT t = forall r. GGConstruct 'Sum (ADTRep t) r constructADT :: forall t. ConstructableADT t => ConstructADT t -> ADT t Expr type DeconstructADT t r = GGDeconstruct 'Sum (ADTRep t) (ADT t Expr) r deconstructADT :: forall t r. (ConstructableADT t, Table Expr r) => DeconstructADT t r type NameADT t = GGName 'Sum (ADTRep t) (ADT t Name) nameADT :: forall t. ConstructableADT t => NameADT t type AggregateADT t = forall r. GGAggregate 'Sum (ADTRep t) r aggregateADT :: forall t. ConstructableADT t => AggregateADT t -> ADT t Expr -> ADT t Aggregate data HKD a f class (Generic a, HTable (GColumns (HKD a)), KnownAlgebra (GAlgebra (Rep a)), Eval (GGTable (GAlgebra (Rep a)) (TTable (Reify Result)) TColumns (Col (Reify Result)) (GRecord (GMap (TColumn (Reify Result)) (Rep a)))), Eval (GGContext (GAlgebra (Rep a)) TUnreifyContext (GRecord (GMap (TColumn (Reify Result)) (Rep a)))) ~ Result, GRecordable (GMap (TColumn (Reify Result)) (Rep a)), GMappable Top (Rep a), GMappable (TTable (Reify Result)) (GMap (TColumn (Reify Result)) (Rep a)), GMap TUnreify (GMap (TColumn (Reify Result)) (Rep a)) ~ GMap (TColumn Result) (Rep a)) => HKDable a type BuildHKD a name = GGBuild (GAlgebra (Rep a)) name (HKDRep a) (HKD a Expr) buildHKD :: forall a name. BuildableHKD a name => BuildHKD a name type ConstructHKD a = forall r. GGConstruct (GAlgebra (Rep a)) (HKDRep a) r constructHKD :: forall a. ConstructableHKD a => ConstructHKD a -> HKD a Expr type DeconstructHKD a r = GGDeconstruct (GAlgebra (Rep a)) (HKDRep a) (HKD a Expr) r deconstructHKD :: forall a r. (ConstructableHKD a, Table Expr r) => DeconstructHKD a r type NameHKD a = GGName (GAlgebra (Rep a)) (HKDRep a) (HKD a Name) nameHKD :: forall a. ConstructableHKD a => NameHKD a type AggregateHKD a = forall r. GGAggregate (GAlgebra (Rep a)) (HKDRep a) r aggregateHKD :: forall a. ConstructableHKD a => AggregateHKD a -> HKD a Expr -> HKD a Aggregate -- | The 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. data TableSchema names TableSchema :: String -> Maybe String -> names -> TableSchema names -- | The name of the table. [name] :: TableSchema names -> String -- | The schema that this table belongs to. If Nothing, whatever is -- on the connection's search_path will be used. [schema] :: TableSchema names -> Maybe String -- | The columns of the table. Typically you would use a a higher-kinded -- data type here, parameterized by the ColumnSchema functor. [columns] :: TableSchema names -> names -- | A 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. data Name a -- | Construct a table in the Name context containing the names of -- all columns. Nested column names will be combined with /. -- -- See also: namesFromLabelsWith. namesFromLabels :: Table Name a => a -- | Construct a table in the Name 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. namesFromLabelsWith :: Table Name a => (NonEmpty String -> String) -> a -- | Typed SQL expressions. data Expr a -- | The 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. class (constraint (Unnullify a), Nullable a) => Sql constraint a -- | Produce an expression from a literal. -- -- Note that you can usually use lit, but litExpr can -- solve problems of inference in polymorphic code. litExpr :: Sql DBType a => a -> Expr a -- | Cast an expression to a different type. Corresponds to a -- CAST() function call. unsafeCastExpr :: Sql DBType b => Expr a -> Expr b -- | Unsafely construct an expression from literal SQL. -- -- This is an escape hatch, and can be used if Rel8 can not adequately -- express the query you need. If you find yourself using this function, -- please let us know, as it may indicate that something is missing from -- Rel8! unsafeLiteral :: String -> Expr a -- | nullify a means a cannot take null as a -- value. class (Nullable a, IsMaybe a ~ 'False) => NotNull a -- | Nullable a means that rel8 is able to check if the -- type a is a type that can take null values or not. class Nullable' (IsMaybe a) a => Nullable a -- | Corresponds to SQL null. null :: DBType a => Expr (Maybe a) -- | 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. nullify :: NotNull a => Expr a -> Expr (Maybe a) -- | Like maybe, but to eliminate null. nullable :: Table Expr b => b -> (Expr a -> b) -> Expr (Maybe a) -> b -- | Like isNothing, but for null. isNull :: Expr (Maybe a) -> Expr Bool -- | Like isJust, but for null. isNonNull :: Expr (Maybe a) -> Expr Bool -- | Lift an operation on non-null values to an operation on -- possibly null values. When given null, mapNull -- f returns null. -- -- This is like fmap for Maybe. mapNull :: DBType b => (Expr a -> Expr b) -> Expr (Maybe a) -> Expr (Maybe b) -- | Lift a binary operation on non-null expressions to an -- equivalent binary operator on possibly null expressions. If -- either of the final arguments are null, liftOpNull -- returns null. -- -- This is like liftA2 for Maybe. liftOpNull :: DBType c => (Expr a -> Expr b -> Expr c) -> Expr (Maybe a) -> Expr (Maybe b) -> Expr (Maybe c) -- | Filter a Query that might return null to a -- Query without any nulls. -- -- Corresponds to catMaybes. catNull :: Expr (Maybe a) -> Query (Expr a) -- | Convert a Expr (Maybe Bool) to a Expr Bool by -- treating Nothing as False. This can be useful when -- combined with where_, which expects a Bool, and -- produces expressions that optimize better than general case analysis. coalesce :: Expr (Maybe Bool) -> Expr Bool -- | Database types that can be compared for equality in queries. If a type -- is an instance of DBEq, it means we can compare expressions for -- equality using the SQL = operator. class DBType a => DBEq a -- | The SQL true literal. true :: Expr Bool -- | The SQL false literal. false :: Expr Bool -- | The SQL NOT operator. not_ :: Expr Bool -> Expr Bool -- | The SQL AND operator. (&&.) :: Expr Bool -> Expr Bool -> Expr Bool infixr 3 &&. -- | Fold AND over a collection of expressions. and_ :: Foldable f => f (Expr Bool) -> Expr Bool -- | The SQL OR operator. (||.) :: Expr Bool -> Expr Bool -> Expr Bool infixr 2 ||. -- | Fold OR over a collection of expressions. or_ :: Foldable f => f (Expr Bool) -> Expr Bool -- | 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 ==?. (==.) :: forall a. Sql DBEq a => Expr a -> Expr a -> Expr Bool infix 4 ==. -- | Test 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 /=?. (/=.) :: forall a. Sql DBEq a => Expr a -> Expr a -> Expr Bool infix 4 /=. -- | Test 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 True conditions. -- -- This corresponds to the SQL = operator, though it will always -- return a Bool. (==?) :: DBEq a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 ==? -- | Test if two expressions are different. -- -- This corresponds to the SQL <> operator, though it will -- always return a Bool. (/=?) :: DBEq a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 /=? -- | Like the SQL IN operator, but implemented by folding over a -- list with ==. and ||.. in_ :: forall a f. (Sql DBEq a, Foldable f) => Expr a -> f (Expr a) -> Expr Bool -- | Eliminate a boolean-valued expression. -- -- Corresponds to bool. boolExpr :: Expr a -> Expr a -> Expr Bool -> Expr a -- | A multi-way ifthenelse 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. caseExpr :: [(Expr Bool, Expr a)] -> Expr a -> Expr a -- | The class of database types that support the <, -- <=, > and >= operators. class DBEq a => DBOrd a -- | Corresponds to the SQL < operator. Note that this differs -- from SQL < as null will sort below any other -- value. For a version of < that exactly matches SQL, see -- (<?). (<.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 <. -- | Corresponds to the SQL <= operator. Note that this differs -- from SQL <= as null will sort below any other -- value. For a version of <= that exactly matches SQL, see -- (<=?). (<=.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 <=. -- | Corresponds to the SQL > operator. Note that this differs -- from SQL > as null will sort below any other -- value. For a version of > that exactly matches SQL, see -- (>?). (>.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 >. -- | Corresponds to the SQL >= operator. Note that this differs -- from SQL > as null will sort below any other -- value. For a version of >= that exactly matches SQL, see -- (>=?). (>=.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 >=. -- | Corresponds to the SQL < operator. Returns null -- if either arguments are null. ( Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 <= operator. Returns null -- if either arguments are null. (<=?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 <=? -- | Corresponds to the SQL > operator. Returns null -- if either arguments are null. (>?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 >? -- | Corresponds to the SQL >= operator. Returns null -- if either arguments are null. (>=?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 >=? -- | Given two expressions, return the expression that sorts less than the -- other. -- -- Corresponds to the SQL least() function. leastExpr :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr a -- | Given two expressions, return the expression that sorts greater than -- the other. -- -- Corresponds to the SQL greatest() function. greatestExpr :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr a -- | This type class exists to allow function to have arbitrary -- arity. It's mostly an implementation detail, and typical uses of -- Function shouldn't need this to be specified. class Function arg res -- | Construct an n-ary function that produces an Expr that when -- called runs a SQL function. function :: Function args result => String -> args -> result -- | Construct a function call for functions with no arguments. nullaryFunction :: Sql DBType a => String -> Expr a -- | Construct an expression by applying an infix binary operator to two -- operands. binaryOperator :: Sql DBType c => String -> Expr a -> Expr b -> Expr c -- | The Query monad allows you to compose a SELECT -- query. This monad has semantics similar to the list ([]) -- monad. data Query a -- | Convert a query to a String containing the query as a -- SELECT statement. showQuery :: Table Expr a => Query a -> String -- | Selects a b means that a is a schema (i.e., a -- Table of Names) for the Expr columns in -- b. class Recontextualize Name Expr names exprs => Selects names exprs -- | Select each row from a table definition. This is equivalent to -- FROM table. each :: Selects names exprs => TableSchema names -> Query exprs -- | Construct a query that returns the given input list of rows. This is -- like folding a list of return statements under union, -- but uses the SQL VALUES expression for efficiency. values :: (Table Expr a, Foldable f) => f a -> Query a -- | 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 guard, but as the -- predicate is separate from the argument, it is easy to use in a -- pipeline of Query transformations. filter :: (a -> Expr Bool) -> a -> Query a -- | Drop any rows that don't match a predicate. where_ expr is -- equivalent to the SQL WHERE expr. where_ :: Expr Bool -> Query () -- | Produce the empty query if the given query returns no rows. -- whereExists is equivalent to WHERE EXISTS in SQL. whereExists :: Query a -> Query () -- | Produce the empty query if the given query returns rows. -- whereNotExists is equivalent to WHERE NOT EXISTS in -- SQL. whereNotExists :: Query a -> Query () -- | Select all distinct rows from a query, removing duplicates. -- distinct q is equivalent to the SQL statement SELECT -- DISTINCT q. distinct :: EqTable a => Query a -> Query a -- | Select 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 -- distinctOnBy. distinctOn :: EqTable b => (a -> b) -> Query a -> Query a -- | Select 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 Order will -- be returned. distinctOnBy :: EqTable b => (a -> b) -> Order a -> Query a -> Query a -- | limit n select at most n rows from a query. -- limit n is equivalent to the SQL LIMIT n. limit :: Word -> Query a -> Query a -- | offset n drops the first n rows from a query. -- offset n is equivalent to the SQL OFFSET n. offset :: Word -> Query a -> Query a -- | Combine the results of two queries of the same type, collapsing -- duplicates. union a b is the same as the SQL statement x -- UNION b. union :: EqTable a => Query a -> Query a -> Query a -- | Combine the results of two queries of the same type, retaining -- duplicates. unionAll a b is the same as the SQL statement -- x UNION ALL b. unionAll :: Table Expr a => Query a -> Query a -> Query a -- | Find the intersection of two queries, collapsing duplicates. -- intersect a b is the same as the SQL statement x -- INTERSECT b. intersect :: EqTable a => Query a -> Query a -> Query a -- | Find the intersection of two queries, retaining duplicates. -- intersectAll a b is the same as the SQL statement x -- INTERSECT ALL b. intersectAll :: EqTable a => Query a -> Query a -> Query a -- | Find the difference of two queries, collapsing duplicates except a -- b is the same as the SQL statement x INTERSECT b. except :: EqTable a => Query a -> Query a -> Query a -- | Find the difference of two queries, retaining duplicates. -- exceptAll a b is the same as the SQL statement x EXCEPT -- ALL b. exceptAll :: EqTable a => Query a -> Query a -> Query a -- | Checks if a query returns at least one row. exists :: Query a -> Query (Expr Bool) -- | with is similar to filter, but allows the predicate to -- be a full query. -- -- with f a = a <$ whereExists (f a), but this form matches -- filter. with :: (a -> Query b) -> a -> Query a -- | Like with, but with a custom membership test. withBy :: (a -> b -> Expr Bool) -> Query b -> a -> Query a -- | Filter rows where a -> Query b yields no rows. without :: (a -> Query b) -> a -> Query a -- | Like without, but with a custom membership test. withoutBy :: (a -> b -> Expr Bool) -> Query b -> a -> Query a -- | An Aggregate a describes how to aggregate Tables of -- type a. You can unpack an Aggregate back to -- a by running it with aggregate. As Aggregate -- is almost an Applicative functor - but there is no pure -- operation. This means Aggregate is an instance of -- Apply, and you can combine Aggregates using the -- . combinator. data Aggregate a -- | Aggregates a b means that the columns in a are all -- Aggregate Exprs for the columns in b. class Recontextualize Aggregate Expr aggregates exprs => Aggregates aggregates exprs -- | Apply an aggregation to all rows returned by a Query. aggregate :: Aggregates aggregates exprs => Query aggregates -> Query exprs -- | Count 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. countRows :: Query a -> Query (Expr Int64) -- | Group equal tables together. This works by aggregating each column in -- the given table with groupByExpr. groupBy :: forall exprs aggregates. (EqTable exprs, Aggregates aggregates exprs) => exprs -> aggregates -- | Aggregate 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 (Item Expr))
--   ordersWithItems = do
--     order <- each orderSchema
--     items aggregate $ listAgg <$ itemsFromOrder order
--     return (order, items)
--   
listAgg :: Aggregates aggregates exprs => exprs -> ListTable aggregates -- | Collect expressions values as a list. listAggExpr :: Sql DBType a => Expr a -> Aggregate [a] -- | Like listAgg, but the result is guaranteed to be a non-empty -- list. nonEmptyAgg :: Aggregates aggregates exprs => exprs -> NonEmptyTable aggregates -- | Collect expressions values as a non-empty list. nonEmptyAggExpr :: Sql DBType a => Expr a -> Aggregate (NonEmpty a) -- | The class of database types that support the max aggregation -- function. class DBOrd a => DBMax a -- | Produce an aggregation for Expr a using the max -- function. max :: Sql DBMax a => Expr a -> Aggregate a -- | The class of database types that support the min aggregation -- function. class DBOrd a => DBMin a -- | Produce an aggregation for Expr a using the max -- function. min :: Sql DBMin a => Expr a -> Aggregate a -- | The class of database types that support the sum() -- aggregation function. class DBType a => DBSum a -- | Corresponds 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 cast -- back to the original input type. This can lead to overflows, and if -- you anticipate very large sums, you should upcast your input. sum :: Sql DBSum a => Expr a -> Aggregate a -- | Take the sum of all expressions that satisfy a predicate. sumWhere :: (Sql DBNum a, Sql DBSum a) => Expr Bool -> Expr a -> Aggregate a -- | The class of data types that support the string_agg() -- aggregation function. class DBType a => DBString a -- | Corresponds to string_agg(). stringAgg :: Sql DBString a => Expr db -> Expr a -> Aggregate a -- | Count the occurances of a single column. Corresponds to -- COUNT(a) count :: Expr a -> Aggregate Int64 -- | Corresponds to COUNT(*). countStar :: Aggregate Int64 -- | Count the number of distinct occurances of a single column. -- Corresponds to COUNT(DISTINCT a) countDistinct :: Sql DBEq a => Expr a -> Aggregate Int64 -- | A count of the number of times a given expression is true. countWhere :: Expr Bool -> Aggregate Int64 -- | Corresponds to bool_and. and :: Expr Bool -> Aggregate Bool -- | Corresponds to bool_or. or :: Expr Bool -> Aggregate Bool -- | Order the rows returned by a query. orderBy :: Order a -> Query a -> Query a -- | An ordering expression for a. Primitive orderings are defined -- with asc and desc, and you can combine Order -- via its various instances. -- -- A common pattern is to use <> to combine multiple -- orderings in sequence, and >$< (from -- Contravariant) to select individual columns. data Order a -- | Sort a column in ascending order. asc :: DBOrd a => Order (Expr a) -- | Sort a column in descending order. desc :: DBOrd a => Order (Expr a) -- | Transform an ordering so that null values appear first. This -- corresponds to NULLS FIRST in SQL. nullsFirst :: Order (Expr a) -> Order (Expr (Maybe a)) -- | Transform an ordering so that null values appear first. This -- corresponds to NULLS LAST in SQL. nullsLast :: Order (Expr a) -> Order (Expr (Maybe a)) -- | 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. class (ToExprs exprs a, a ~ FromExprs exprs) => Serializable exprs a | exprs -> a -- | ToExprs exprs a is evidence that the types exprs and -- a describe essentially the same type, but exprs is -- in the Expr context, and a is in the Result -- context. class Table Expr exprs => ToExprs exprs a fromResult :: ToExprs exprs a => Columns exprs (Col Result) -> a toResult :: ToExprs exprs a => a -> Columns exprs (Col Result) fromResult :: (ToExprs exprs a, Generic (Record a), KnownAlgebra (GAlgebra (Rep (Record exprs))), Eval (GGToExprs (GAlgebra (Rep (Record exprs))) TToExprs TColumns (Rep (Record exprs)) (Rep (Record a))), Columns exprs ~ Eval (GGColumns (GAlgebra (Rep (Record exprs))) TColumns (Rep (Record exprs)))) => Columns exprs (Col Result) -> a toResult :: (ToExprs exprs a, Generic (Record a), KnownAlgebra (GAlgebra (Rep (Record exprs))), Eval (GGToExprs (GAlgebra (Rep (Record exprs))) TToExprs TColumns (Rep (Record exprs)) (Rep (Record a))), Columns exprs ~ Eval (GGColumns (GAlgebra (Rep (Record exprs))) TColumns (Rep (Record exprs)))) => a -> Columns exprs (Col Result) -- | The FromExprs type function maps a type in the Expr -- context to the corresponding type in the Result context. type family FromExprs a -- | The Result 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. data Result a -- | Run a SELECT query, returning all rows. select :: forall exprs a. Serializable exprs a => Connection -> Query exprs -> IO [a] -- | The constituent parts of a SQL INSERT statement. data Insert a [Insert] :: Selects names exprs => {into :: TableSchema names " Which table to insert into.", rows :: [exprs] " The rows to insert.", onConflict :: OnConflict " What to do if the inserted rows conflict with data already in the table.", returning :: Returning names a " What information to return on completion."} -> Insert a -- | OnConflict allows you to add an ON CONFLICT clause -- to an INSERT statement. data OnConflict -- |
--   ON CONFLICT ABORT
--   
Abort :: OnConflict -- |
--   ON CONFLICT DO NOTHING
--   
DoNothing :: OnConflict -- | Run an INSERT statement insert :: Connection -> Insert a -> IO a -- | The constituent parts of a DELETE statement. data Delete a [Delete] :: Selects names exprs => {from :: TableSchema names " Which table to delete from.", deleteWhere :: exprs -> Expr Bool " Which rows should be selected for deletion.", returning :: Returning names a " What to return from the @DELETE@ statement."} -> Delete a -- | Run a DELETE statement. delete :: Connection -> Delete a -> IO a -- | Run an UPDATE statement. update :: Connection -> Update a -> IO a -- | The constituent parts of an UPDATE statement. data Update a [Update] :: Selects names exprs => {target :: TableSchema names " Which table to update.", set :: exprs -> exprs " How to update each selected row.", updateWhere :: exprs -> Expr Bool " Which rows to select for update.", returning :: Returning names a " What to return from the @UPDATE@ statement."} -> Update a -- | INSERT, UPDATE and DELETE all support -- returning either the number of rows affected, or the actual rows -- modified. Projection allows you to project out of these -- returned 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 as a default value). data Returning names a [NumberOfRowsAffected] :: Returning names Int64 [Projection] :: (Selects names exprs, Serializable projection a) => (exprs -> projection) -> Returning names [a] -- | Given a TableSchema and Query, 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. createView :: Selects names exprs => TableSchema names -> Query exprs -> Connection -> IO () -- | See -- https://www.postgresql.org/docs/current/functions-sequence.html nextval :: String -> Expr Int64 -- | Some PostgreSQL functions, such as nextval, have side effects, -- breaking the referential transparency we would otherwise enjoy. -- -- To try to recover our ability to reason about such expressions, -- Evaluate allows us to control the evaluation order of -- side-effects by sequencing them monadically. data Evaluate a -- | eval takes expressions that could potentially have side effects -- and "runs" them in the Evaluate monad. The returned expressions -- have no side effetcs and can safely be reused. eval :: Table Expr a => a -> Evaluate a -- | evaluate runs an Evaluate inside the Query monad. evaluate :: Evaluate a -> Query a -- | The Labelable class is an internal implementation detail of -- Rel8, and indicates that we can successfully "name" all columns in a -- type. class Interpretation context => Labelable context newtype HKDT a HKDT :: a -> HKDT a [unHKDT] :: HKDT a -> a