-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Hey! Hey! Can u rel8? @package rel8 @version 1.7.0.0 module Rel8.Decoder data Decoder a Decoder :: Value a -> Parser a -> Decoder a -- | How to deserialize from PostgreSQL's binary format. [binary] :: Decoder a -> Value a -- | How to deserialize from PostgreSQL's text format. [text] :: Decoder a -> Parser a type Parser a = ByteString -> Either String a -- | Apply a parser to Decoder. -- -- This can be used if the data stored in the database should only be -- subset of a given Decoder. The parser is applied when -- deserializing rows returned. parseDecoder :: (a -> Either String b) -> Decoder a -> Decoder b module Rel8.Encoder data Encoder a Encoder :: Value a -> (a -> Builder) -> (a -> PrimExpr) -> Encoder a -- | How to serialize to PostgreSQL's binary format. [binary] :: Encoder a -> Value a -- | How to serialize to PostgreSQL's text format. [text] :: Encoder a -> a -> Builder -- | How to encode a single Haskell value as an SQL expression. [quote] :: Encoder a -> a -> PrimExpr 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 -- | like x y corresponds to the expression y LIKE x. -- -- Note that the arguments to like are swapped. This is to aid -- currying, so you can write expressions like filter (like "Rel%" . -- packageName) =<< each haskellPackages like :: Expr Text -> Expr Text -> Expr Bool -- | ilike x y corresponds to the expression y ILIKE x. -- -- Note that the arguments to ilike are swapped. This is to aid -- currying, so you can write expressions like filter (ilike "Rel%" . -- packageName) =<< each haskellPackages ilike :: Expr Text -> Expr Text -> Expr Bool 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, -- this can be useful to convert Expr Float to Expr -- Double. realToFrac :: (Sql DBNum a, Sql DBFractional b, Homonullable a b) => Expr a -> Expr b -- | Emulates the behaviour of the Haskell function div in -- PostgreSQL. div :: Sql DBIntegral a => Expr a -> Expr a -> Expr a -- | Emulates the behaviour of the Haskell function mod in -- PostgreSQL. mod :: Sql DBIntegral a => Expr a -> Expr a -> Expr a -- | Simultaneous div and mod. divMod :: Sql DBIntegral a => Expr a -> Expr a -> (Expr a, Expr a) -- | Perform integral division. Corresponds to the div() function -- in PostgreSQL, which behaves like Haskell's quot rather than -- div. quot :: Sql DBIntegral a => Expr a -> Expr a -> Expr a -- | Corresponds to the mod() function in PostgreSQL, which -- behaves like Haskell's rem rather than mod. rem :: Sql DBIntegral a => Expr a -> Expr a -> Expr a -- | Simultaneous quot and rem. quotRem :: Sql DBIntegral a => Expr 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.Array -- | A ListTable value contains zero or more instances of -- a. You construct ListTables with many or -- listAgg. data ListTable (context :: Context) a -- | Get the first element of a ListTable (or nullTable if -- empty). head :: Table Expr a => ListTable Expr a -> NullTable Expr a headExpr :: Sql DBType a => Expr [a] -> Expr (Nullify a) -- | index i as extracts a single element from as, -- returning nullTable if i is out of range. Note that -- although PostgreSQL array indexes are 1-based (by default), this -- function is always 0-based. index :: Table Expr a => Expr Int32 -> ListTable Expr a -> NullTable Expr a indexExpr :: Sql DBType a => Expr Int32 -> Expr [a] -> Expr (Nullify a) -- | Get the last element of a ListTable (or nullTable if -- empty). last :: Table Expr a => ListTable Expr a -> NullTable Expr a lastExpr :: Sql DBType a => Expr [a] -> Expr (Nullify a) -- | Get the length of a ListTable length :: Table Expr a => ListTable Expr a -> Expr Int32 lengthExpr :: Expr [a] -> Expr Int32 -- | elem a as tests whether a is an element of -- the list as. elem :: Sql DBEq a => Expr a -> Expr [a] -> Expr Bool infix 4 `elem` -- | A NonEmptyTable value contains one or more instances of -- a. You construct NonEmptyTables with some or -- nonEmptyAgg. data NonEmptyTable (context :: Context) a -- | Get the first element of a NonEmptyTable. head1 :: Table Expr a => NonEmptyTable Expr a -> a head1Expr :: Sql DBType a => Expr (NonEmpty a) -> Expr a -- | index1 i as extracts a single element from -- as, returning nullTable if i is out of range. -- Note that although PostgreSQL array indexes are 1-based (by default), -- this function is always 0-based. index1 :: Table Expr a => Expr Int32 -> NonEmptyTable Expr a -> NullTable Expr a index1Expr :: Sql DBType a => Expr Int32 -> Expr (NonEmpty a) -> Expr (Nullify a) -- | Get the last element of a NonEmptyTable. last1 :: Table Expr a => NonEmptyTable Expr a -> a last1Expr :: Sql DBType a => Expr (NonEmpty a) -> Expr a -- | Get the length of a NonEmptyTable length1 :: Table Expr a => NonEmptyTable Expr a -> Expr Int32 length1Expr :: Expr (NonEmpty a) -> Expr Int32 -- | elem1 a as tests whether a is an element of -- the non-empty list as. elem1 :: Sql DBEq a => Expr a -> Expr (NonEmpty a) -> Expr Bool infix 4 `elem1` -- | unsafeSubscript a i will generate the SQL -- a[i]. -- -- Note that this function is not type checked and the generated SQL has -- no casts. This is only intended an escape hatch to be used if Rel8 -- cannot otherwise 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! unsafeSubscript :: Sql DBType b => Expr a -> Expr i -> Expr b -- | unsafeSubscripts a (i, j) will generate the SQL -- a[i][j]. -- -- Note that this function is not type checked and the generated SQL has -- no casts. This is only intended an escape hatch to be used if Rel8 -- cannot otherwise 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! unsafeSubscripts :: (Table Expr i, Sql DBType b) => Expr a -> i -> Expr b -- | Rel8.Tabulate provides an alternative API (Tabulation) -- for writing queries that complements the main Rel8 API -- (Query). module Rel8.Tabulate -- | A Tabulation k a is like a Query a, -- except that each row also has a key k in addition to the -- value a. Tabulations can be composed monadically just -- like Querys, but the resulting join is more like a NATURAL -- JOIN (based on the common key column(s) k) than the -- CROSS JOIN given by Query. -- -- Another way to think of Tabulation k a is as analogous -- to Map k a in the same way Query a is -- analogous to [a]. However, there's nothing stopping a -- Tabulation from containing multiple rows with the same key, so -- technically Map k (NonEmpty a) is more accurate. -- -- Tabulations can be created from Querys with -- fromQuery and liftQuery and converted back to -- Querys with lookup and toQuery (though note the -- caveats that come with the latter). data Tabulation k a -- | Any Query of key-value pairs (k, a) can be a -- Tabulation k a. fromQuery :: Query (k, a) -> Tabulation k a -- | Convert a Tabulation k a back into a Query of -- key-value pairs. -- -- Note that the result of a toQuery is undefined (will always -- return zero rows) on Tabulations constructed with -- liftQuery or pure. So while toQuery . fromQuery -- is always id, fromQuery . toQuery is not. -- -- A safer, more predictable alternative to toQuery is to use -- lookup with an explicit set of keys: -- --
--   do
--      k <- keys
--      a <- lookup k tabulation
--      pure (k, a)
--   
-- -- Having said that, in practice, most legitimate uses of -- Tabulation will have a well-defined toQuery. 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 -- do-notation, which is the main benefit of having -- Tabulation as a monad in the first place. -- -- In particular, toQuery t is well-defined for any -- Tabulation t defined as t = fromQuery _. -- toQuery t is also well-defined for any -- Tabulation t defined as t = t' >>= _ or -- t = t' *> _ where toQuery t' is -- well-defined. There are other valid permutations too. Generally, -- anything that uses fromQuery at some point, unless wrapped in a -- top-level present or absent, will have a well-defined -- toQuery. toQuery :: Table Expr k => Tabulation k a -> Query (k, a) -- | A Query a can be treated as a Tabulation k -- a where the given a values exist at every possible key -- k. liftQuery :: Query a -> Tabulation k a -- | Run a Kleisli arrow in the the Query monad "through" a -- Tabulation. Useful for filtering a Tabulation. -- --
--   filter ((>=. 30) . userAge) `through' usersById
--   
through :: (a -> Query b) -> Tabulation k a -> Tabulation k b infixr 1 `through` -- | lookup k t returns the value(s) at the key k -- in the tabulation t. lookup :: EqTable k => k -> Tabulation k a -> Query a -- | aggregate produces a "magic" Tabulation whereby the -- values within each group of keys in the given Tabulation 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. aggregate :: (EqTable k, Table Expr i, Table Expr a) => Aggregator i a -> Tabulation k i -> Tabulation k a -- | aggregate1 aggregates the values within each key of a -- Tabulation. There is an implicit GROUP BY on all the -- key columns. aggregate1 :: forall k i (fold :: Fold) a. (EqTable k, Table Expr i) => Aggregator' fold i a -> Tabulation k i -> Tabulation k a -- | distinct ensures a Tabulation 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 order. distinct :: EqTable k => Tabulation k a -> Tabulation k a -- | order orders the values of a Tabulation within -- their respective keys. This specifies a defined order for -- distinct. It also defines the order of the lists produced by -- many and some. order :: OrdTable k => Order a -> Tabulation k a -> Tabulation k a -- | materialize for Tabulations. materialize :: (Table Expr k, Table Expr a) => Tabulation k a -> (Tabulation k a -> Query b) -> Query b -- | count returns a count of how many entries are in the given -- Tabulation at each key. -- -- The resulting Tabulation is "magic" in that the value -- 0 exists at every possible key that wasn't in the given -- Tabulation. count :: EqTable k => Tabulation k a -> Tabulation k (Expr Int64) -- | optional produces a "magic" Tabulation whereby each -- entry in the given Tabulation is wrapped in justTable, -- and every other possible key contains a single nothingTable. -- -- This is used to implement leftAlignWith. optional :: Tabulation k a -> Tabulation k (MaybeTable Expr a) -- | many aggregates each entry with a particular key into a single -- entry with all of the values contained in a ListTable. -- -- order can be used to give this ListTable a defined -- order. -- -- The resulting Tabulation is "magic" in that the value -- 'Rel8.listTable []' exists at every possible key that wasn't -- in the given Tabulation. many :: (EqTable k, Table Expr a) => Tabulation k a -> Tabulation k (ListTable Expr a) -- | some aggregates each entry with a particular key into a single -- entry with all of the values contained in a NonEmptyTable. -- -- order can be used to give this NonEmptyTable a defined -- order. some :: (EqTable k, Table Expr a) => Tabulation k a -> Tabulation k (NonEmptyTable Expr a) -- | exists produces a "magic" Tabulation which contains the -- value true at each key in the given Tabulation, and the -- value false at every other possible key. exists :: Tabulation k a -> Tabulation k (Expr Bool) -- | present produces a Tabulation where a single () -- row exists for every key that was present in the given -- Tabulation. -- -- This is used to implement similarity. present :: Tabulation k a -> Tabulation k () -- | absent produces a Tabulation where a single () -- row exists at every possible key that absent from the given -- Tabulation. -- -- This is used to implement difference. absent :: Tabulation k a -> Tabulation k () -- | Performs a NATURAL FULL OUTER JOIN based on the common key -- columns. -- -- Analogous to align. align :: EqTable k => Tabulation k a -> Tabulation k b -> Tabulation k (TheseTable Expr a b) -- | Performs a NATURAL FULL OUTER JOIN based on the common key -- columns. -- -- Analogous to alignWith. alignWith :: EqTable k => (TheseTable Expr a b -> c) -> Tabulation k a -> Tabulation k b -> Tabulation k c -- | Performs a NATURAL LEFT OUTER JOIN based on the common key -- columns. -- -- Analogous to rpadZip. -- -- Note that you can achieve the same effect with optional and the -- Applicative instance for Tabulation, i.e., this is just -- \left right -> liftA2 (,) left (optional right). You can -- also use do-notation. leftAlign :: EqTable k => Tabulation k a -> Tabulation k b -> Tabulation k (a, MaybeTable Expr b) -- | Performs a NATURAL LEFT OUTER JOIN based on the common key -- columns. -- -- Analogous to rpadZipWith. -- -- Note that you can achieve the same effect with optional and the -- Applicative instance for Tabulation, i.e., this is just -- \f left right -> liftA2 f left (optional right). You can -- also use do-notation. leftAlignWith :: EqTable k => (a -> MaybeTable Expr b -> c) -> Tabulation k a -> Tabulation k b -> Tabulation k c -- | Performs a NATURAL RIGHT OUTER JOIN based on the common key -- columns. -- -- Analogous to lpadZip. -- -- Note that you can achieve the same effect with optional and the -- Applicative instance for Tabulation, i.e., this is just -- \left right -> liftA2 (flip (,)) right (optional left). -- You can also use do-notation. rightAlign :: EqTable k => Tabulation k a -> Tabulation k b -> Tabulation k (MaybeTable Expr a, b) -- | Performs a NATURAL RIGHT OUTER JOIN based on the common key -- columns. -- -- Analogous to lpadZipWith. -- -- Note that you can achieve the same effect with optional and the -- Applicative instance for Tabulation, i.e., this is just -- \f left right -> liftA2 (flip f) right (optional left). -- You can also use do-notation. rightAlignWith :: EqTable k => (MaybeTable Expr a -> b -> c) -> Tabulation k a -> Tabulation k b -> Tabulation k c -- | Performs a NATURAL INNER JOIN based on the common key -- columns. -- -- Analagous to zip. -- -- Note that you can achieve the same effect with the Applicative -- instance of Tabulation, i.e., this is just 'liftA2 -- (,)'. You can also use do-notation. zip :: EqTable k => Tabulation k a -> Tabulation k b -> Tabulation k (a, b) -- | Performs a NATURAL INNER JOIN based on the common key -- columns. -- -- Analagous to zipWith. -- -- Note that you can achieve the same effect with the Applicative -- instance of Tabulation, i.e., this is just -- liftA2. You can also use do-notation. zipWith :: EqTable k => (a -> b -> c) -> Tabulation k a -> Tabulation k b -> Tabulation k c -- | Performs a NATURAL 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. -- -- Note that you can achieve a similar effect with present and the -- Applicative instance of Tabulation, i.e., this is just -- \left right -> left <* present right. You can also use -- do-notation. similarity :: EqTable k => Tabulation k a -> Tabulation k b -> Tabulation k a -- | Performs a NATURAL 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. -- -- Note that you can achieve a similar effect with absent and the -- Applicative instance of Tabulation, i.e., this is just -- \left right -> left <* absent right. You can also use -- do-notation. difference :: EqTable k => Tabulation k a -> Tabulation k b -> Tabulation k a instance Rel8.Table.Eq.EqTable k => Rel8.Table.Alternative.AltTable (Rel8.Tabulate.Tabulation k) instance Rel8.Table.Eq.EqTable k => Rel8.Table.Alternative.AlternativeTable (Rel8.Tabulate.Tabulation k) instance Rel8.Table.Eq.EqTable k => GHC.Base.Applicative (Rel8.Tabulate.Tabulation k) instance Rel8.Table.Eq.EqTable k => Data.Functor.Bind.Class.Apply (Rel8.Tabulate.Tabulation k) instance Data.Bifunctor.Bifunctor Rel8.Tabulate.Tabulation instance Rel8.Table.Eq.EqTable k => Data.Functor.Bind.Class.Bind (Rel8.Tabulate.Tabulation k) instance Rel8.Table.Projection.Biprojectable Rel8.Tabulate.Tabulation instance Data.Functor.Contravariant.Contravariant Rel8.Tabulate.Predicate instance GHC.Base.Functor (Rel8.Tabulate.Tabulation k) instance Rel8.Table.Eq.EqTable k => GHC.Base.Monad (Rel8.Tabulate.Tabulation k) instance GHC.Base.Monoid (Rel8.Tabulate.Predicate k) instance (Rel8.Table.Eq.EqTable k, Rel8.Table.Table Rel8.Expr.Expr a, GHC.Base.Semigroup a) => GHC.Base.Monoid (Rel8.Tabulate.Tabulation k a) instance Rel8.Table.Projection.Projectable (Rel8.Tabulate.Tabulation k) instance GHC.Base.Semigroup (Rel8.Tabulate.Predicate k) instance (Rel8.Table.Eq.EqTable k, Rel8.Table.Table Rel8.Expr.Expr a, GHC.Base.Semigroup a) => GHC.Base.Semigroup (Rel8.Tabulate.Tabulation k a) 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 => QualifiedName -- | 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 :: 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 => 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 ($dmenumValue) :: (DBEnum a, Enumable a) => a -> String -- | The name of the PostgreSQL enum type that a maps to. enumTypeName :: DBEnum a => QualifiedName -- | List of all possible values of the enum type. enumerate :: DBEnum a => [a] ($dmenumerate) :: (DBEnum a, Enumable a) => [a] -- | 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 :: Encoder a -> Decoder a -> Char -> TypeName -> TypeInformation a -- | How to serialize a Haskell value to PostgreSQL. [encode] :: TypeInformation a -> Encoder a -- | How to deserialize a PostgreSQL result back to Haskell. [decode] :: TypeInformation a -> Decoder a -- | The delimiter that is used in PostgreSQL's text format in arrays of -- this type (this is almost always ','). [delimiter] :: TypeInformation a -> Char -- | The name of the SQL type. [typeName] :: TypeInformation a -> TypeName -- | A PostgreSQL type consists of a QualifiedName (name, schema), -- and optional modifiers and arrayDepth. modifiers -- will usually be [], but a type like numeric(6, 2) -- will have ["6", "2"]. arrayDepth is always 0 -- for non-array types. data TypeName TypeName :: QualifiedName -> [String] -> Word -> TypeName -- | The name (and schema) of the type. [name] :: TypeName -> QualifiedName -- | Any modifiers applied to the underlying type. [modifiers] :: TypeName -> [String] -- | If this is an array type, the depth of that array (1 for -- [], 2 for [][], etc). [arrayDepth] :: TypeName -> Word -- | 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, DBOrd 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 DeriveAnyClass 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 :: Rel8able) -- | 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 :: Context) a type family HADT (context :: Context) (t :: Rel8able) -- | 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 :: Context) = (either :: Type -> Type -> Type) | either -> 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 :: Context) = (maybe :: Type -> Type) | maybe -> 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 :: Context) = (list :: Type -> Type) | list -> 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 :: Context) = (nonEmpty :: Type -> Type) | nonEmpty -> context -- | Nest a Null value within a Rel8able. HNull f -- a will produce a NullTable a in the Expr -- context, and a Maybe a in the Result context. type family HNull (context :: Context) = (maybe :: Type -> Type) | maybe -> 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 :: Context) = (these :: Type -> Type -> Type) | these -> context type family Lift (context :: 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, a ~ Transpose context a) => Table (context :: Context) a | a -> context where { -- | The HTable functor that describes the schema of this table. type Columns a :: HTable; -- | The common context that all columns use as an interpretation. type Context a :: Context; -- | The FromExprs type family maps a type in the Expr -- context to the corresponding Haskell type. type FromExprs a; type Transpose (context' :: Context) a; type Columns a = GColumns TColumns Rep Record a; type Context a = GContext TContext Rep Record a; type FromExprs a = Map TFromExprs a; type Transpose context' :: Context a = Map TTranspose context' a; } toColumns :: Table context a => a -> Columns a context ($dmtoColumns) :: (Table context a, Generic (Record a), GTable (TTable context) TColumns (Rep (Record a)), Columns a ~ GColumns TColumns (Rep (Record a))) => a -> Columns a context fromColumns :: Table context a => Columns a context -> a ($dmfromColumns) :: (Table context a, Generic (Record a), GTable (TTable context) TColumns (Rep (Record a)), Columns a ~ GColumns TColumns (Rep (Record a))) => Columns a context -> a fromResult :: Table context a => Columns a Result -> FromExprs a ($dmfromResult) :: (Table context a, Generic (Record (FromExprs a)), GSerialize TSerialize TColumns (Rep (Record a)) (Rep (Record (FromExprs a))), Columns a ~ GColumns TColumns (Rep (Record a))) => Columns a Result -> FromExprs a toResult :: Table context a => FromExprs a -> Columns a Result ($dmtoResult) :: (Table context a, Generic (Record (FromExprs a)), GSerialize TSerialize TColumns (Rep (Record a)) (Rep (Record (FromExprs a))), Columns a ~ GColumns TColumns (Rep (Record a))) => FromExprs a -> Columns a Result -- | 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 :: HTable) -- | Transposes from to a b means that a and -- b are Tables, 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). class (Table from a, Table to b, Congruent a b, b ~ Transpose to a, a ~ Transpose from b) => Transposes (from :: Context) (to :: Context) 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 :: Type -> Type) -- | 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 :: Type -> Type) -- | 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 eqTable :: EqTable a => Columns a (Dict (Sql DBEq)) ($dmeqTable) :: (EqTable a, GTable TEqTable TColumns (Rep (Record a)), Columns a ~ GColumns TColumns (Rep (Record a))) => Columns a (Dict (Sql DBEq)) -- | Compare two Tables for equality. This corresponds to comparing -- all columns inside each table for equality, and combining all -- comparisons with AND. (==:) :: 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. (/=:) :: 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 ordTable :: OrdTable a => Columns a (Dict (Sql DBOrd)) ($dmordTable) :: (OrdTable a, GTable TOrdTable TColumns (Rep (Record a)), Columns a ~ GColumns TColumns (Rep (Record a))) => Columns a (Dict (Sql DBOrd)) -- | Test if one Table sorts before another. Corresponds to -- comparing all columns with <. (<:) :: OrdTable a => a -> a -> Expr Bool infix 4 <: -- | Test if one Table sorts before, or is equal to, another. -- Corresponds to comparing all columns with <=. (<=:) :: OrdTable a => a -> a -> Expr Bool infix 4 <=: -- | Test if one Table sorts after another. Corresponds to -- comparing all columns with >. (>:) :: OrdTable a => a -> a -> Expr Bool infix 4 >: -- | Test if one Table sorts after another. Corresponds to -- comparing all columns with >=. (>=:) :: OrdTable a => a -> a -> Expr Bool infix 4 >=: -- | Construct an Order for a Table by sorting all columns -- into ascending orders (any nullable columns will be sorted with -- NULLS FIRST). ascTable :: 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 :: OrdTable a => Order a -- | Given two Tables, return the table that sorts after the -- other. greatest :: OrdTable a => a -> a -> a -- | Given two Tables, return the table that sorts before the -- other. least :: OrdTable a => a -> a -> a -- | Use lit to turn literal Haskell values into expressions. -- lit is capable of lifting single Exprs to full -- tables. lit :: 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 -- | Transform 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. castTable :: Table Expr 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 (context :: Context) a -- | Perform case analysis on a MaybeTable. Like maybe. maybeTable :: Table Expr b => b -> (a -> b) -> MaybeTable Expr 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 Expr a -> Expr (Nullify b) infixl 4 $? -- | The null table. Like Nothing. nothingTable :: Table Expr a => MaybeTable Expr a -- | Lift any table into MaybeTable. Like Just. Note you can -- also use pure. justTable :: a -> MaybeTable Expr a -- | Check if a MaybeTable is absent of any row. Like -- isNothing. isNothingTable :: MaybeTable Expr a -> Expr Bool -- | Check if a MaybeTable contains a row. Like isJust. isJustTable :: MaybeTable Expr a -> Expr Bool -- | fromMaybe for MaybeTables. fromMaybeTable :: Table Expr a => a -> MaybeTable Expr a -> a -- | 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 Expr 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 Expr 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 Expr a -> Query (MaybeTable Expr b) -- | Lift an Aggregator to operate on a MaybeTable. If the -- input query has justTable is, they are folded into a -- single a by the given aggregator — in the case where the -- input query is all nothingTables, the Aggregator's -- fallback a is returned. aggregateJustTable :: forall a i (fold :: Fold). Table Expr a => Aggregator i a -> Aggregator' fold (MaybeTable Expr i) a -- | Lift an Aggregator1 to operate on a MaybeTable. If the -- input query has justTable is, they are folded into a -- single justTable a by the given aggregator — in the -- case where the input query is all nothingTables, a single -- nothingTable row is returned. aggregateJustTable1 :: forall a (fold :: Fold) i (fold' :: Fold). Table Expr a => Aggregator' fold i a -> Aggregator' fold' (MaybeTable Expr i) (MaybeTable Expr a) -- | Lift an aggregator to operate on a MaybeTable. -- nothingTables and justTables are grouped separately. aggregateMaybeTable :: forall (fold :: Fold) i a. Aggregator' fold i a -> Aggregator1 (MaybeTable Expr i) (MaybeTable Expr a) -- | 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 Name 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 (context :: Context) a b -- | Pattern match/eliminate an EitherTable, by providing mappings -- from a leftTable and rightTable. eitherTable :: Table Expr c => (a -> c) -> (b -> c) -> EitherTable Expr a b -> c -- | Construct a left EitherTable. Like Left. leftTable :: Table Expr b => a -> EitherTable Expr a b -- | Construct a right EitherTable. Like Right. rightTable :: Table Expr a => b -> EitherTable Expr a b -- | Test if an EitherTable is a leftTable. isLeftTable :: EitherTable Expr a b -> Expr Bool -- | Test if an EitherTable is a rightTable. isRightTable :: EitherTable Expr a b -> Expr Bool -- | Filter EitherTables, keeping only leftTables. keepLeftTable :: EitherTable Expr a b -> Query a -- | Filter EitherTables, keeping only rightTables. keepRightTable :: EitherTable Expr 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 Expr a b -> Query (EitherTable Expr c d) -- | Lift an Aggregator to operate on an EitherTable. If the -- input query has leftTable as, they are folded into a -- single c by the given aggregator — in the case where the -- input query is all rightTables, the Aggregator's -- fallback c is returned. aggregateLeftTable :: forall c a (fold :: Fold) b. Table Expr c => Aggregator a c -> Aggregator' fold (EitherTable Expr a b) c -- | Lift an Aggregator1 to operate on an EitherTable. If the -- input query has leftTable as, they are folded into a -- single justTable c by the given aggregator — in the -- case where the input query is all rightTables, a single -- nothingTable row is returned. aggregateLeftTable1 :: forall c (fold :: Fold) a (fold' :: Fold) b. Table Expr c => Aggregator' fold a c -> Aggregator' fold' (EitherTable Expr a b) (MaybeTable Expr c) -- | Lift an Aggregator to operate on an EitherTable. If the -- input query has rightTable bs, they are folded into a -- single c by the given aggregator — in the case where the -- input query is all rightTables, the Aggregator's -- fallback c is returned. aggregateRightTable :: forall c b (fold :: Fold) a. Table Expr c => Aggregator b c -> Aggregator' fold (EitherTable Expr a b) c -- | Lift an Aggregator1 to operate on an EitherTable. If the -- input query has rightTable bs, they are folded into a -- single justTable c by the given aggregator — in the -- case where the input query is all leftTables, a single -- nothingTable row is returned. aggregateRightTable1 :: forall c (fold :: Fold) a (fold' :: Fold) b. Table Expr c => Aggregator' fold a c -> Aggregator' fold' (EitherTable Expr a b) (MaybeTable Expr c) -- | Lift a pair aggregators to operate on an EitherTable. -- leftTables and rightTables are grouped separately. aggregateEitherTable :: forall (fold :: Fold) i a (fold' :: Fold) i' b. Aggregator' fold i a -> Aggregator' fold' i' b -> Aggregator1 (EitherTable Expr i i') (EitherTable Expr a b) -- | 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 Name 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 (context :: Context) a b -- | Pattern match on a TheseTable. Corresponds to these. theseTable :: Table Expr c => (a -> c) -> (b -> c) -> (a -> b -> c) -> TheseTable Expr a b -> c -- | Construct a TheseTable. Corresponds to This. thisTable :: Table Expr b => a -> TheseTable Expr a b -- | Construct a TheseTable. Corresponds to That. thatTable :: Table Expr a => b -> TheseTable Expr a b -- | Construct a TheseTable. Corresponds to These. thoseTable :: a -> b -> TheseTable Expr a b -- | Test if a TheseTable was constructed with thisTable. -- -- Corresponds to isThis. isThisTable :: TheseTable Expr a b -> Expr Bool -- | Test if a TheseTable was constructed with thatTable. -- -- Corresponds to isThat. isThatTable :: TheseTable Expr a b -> Expr Bool -- | Test if a TheseTable was constructed with thoseTable. -- -- Corresponds to isThese. isThoseTable :: TheseTable Expr a b -> Expr Bool -- | Test if the a side of TheseTable a b is present. -- -- Corresponds to hasHere. hasHereTable :: TheseTable Expr a b -> Expr Bool -- | Test if the b table of TheseTable a b is present. -- -- Corresponds to hasThere. hasThereTable :: TheseTable Expr a b -> Expr Bool -- | Attempt to project out the a table of a TheseTable a -- b. -- -- Corresponds to justHere. justHereTable :: forall (context :: Context) a b. TheseTable context a b -> MaybeTable context a -- | Attempt to project out the b table of a TheseTable a -- b. -- -- Corresponds to justThere. justThereTable :: forall (context :: Context) a b. TheseTable context a b -> MaybeTable context b -- | Construct a TheseTable from two MaybeTables. alignMaybeTable :: MaybeTable Expr a -> MaybeTable Expr b -> MaybeTable Expr (TheseTable Expr a b) -- | Corresponds to a FULL OUTER JOIN between two queries. alignBy :: (a -> b -> Expr Bool) -> Query a -> Query b -> Query (TheseTable Expr a b) keepHereTable :: TheseTable Expr a b -> Query (a, MaybeTable Expr b) loseHereTable :: TheseTable Expr a b -> Query b keepThereTable :: TheseTable Expr a b -> Query (MaybeTable Expr a, b) loseThereTable :: TheseTable Expr a b -> Query a keepThisTable :: TheseTable Expr a b -> Query a loseThisTable :: TheseTable Expr a b -> Query (MaybeTable Expr a, b) keepThatTable :: TheseTable Expr a b -> Query b loseThatTable :: TheseTable Expr a b -> Query (a, MaybeTable Expr b) keepThoseTable :: TheseTable Expr a b -> Query (a, b) loseThoseTable :: TheseTable Expr a b -> Query (EitherTable Expr a b) bitraverseTheseTable :: (a -> Query c) -> (b -> Query d) -> TheseTable Expr a b -> Query (TheseTable Expr c d) -- | Lift an Aggregator to operate on a TheseTable. If the -- input query has thisTable as, they are folded into a -- single c by the given aggregator — in the case where the -- input query is all thatTables or thoseTables, the -- Aggregator's fallback c is returned. aggregateThisTable :: forall c a (fold :: Fold) b. Table Expr c => Aggregator a c -> Aggregator' fold (TheseTable Expr a b) c -- | Lift an Aggregator1 to operate on a TheseTable. If the -- input query has thisTable as, they are folded into a -- single justTable c by the given aggregator — in the -- case where the input query is all thatTables or -- thoseTables, a single nothingTable row is returned. aggregateThisTable1 :: forall c (fold :: Fold) a (fold' :: Fold) b. Table Expr c => Aggregator' fold a c -> Aggregator' fold' (TheseTable Expr a b) (MaybeTable Expr c) -- | Lift an Aggregator to operate on a TheseTable. If the -- input query has thatTable bs, they are folded into a -- single c by the given aggregator — in the case where the -- input query is all thisTables or thoseTables, the -- Aggregator's fallback c is returned. aggregateThatTable :: forall c b (fold :: Fold) a. Table Expr c => Aggregator b c -> Aggregator' fold (TheseTable Expr a b) c -- | Lift an Aggregator1 to operate on a TheseTable. If the -- input query has thatTable bs, they are folded into a -- single justTable c by the given aggregator — in the -- case where the input query is all thisTables or -- thoseTables, a single nothingTable row is returned. aggregateThatTable1 :: forall c (fold :: Fold) b (fold' :: Fold) a. Table Expr c => Aggregator' fold b c -> Aggregator' fold' (TheseTable Expr a b) (MaybeTable Expr c) -- | Lift an Aggregator to operate on a ThoseTable. If the -- input query has thoseTable a bs, they are folded into -- a single c by the given aggregator — in the case where the -- input query is all thisTables or thatTables, the -- Aggregator's fallback c is returned. aggregateThoseTable :: forall c a b (fold :: Fold). Table Expr c => Aggregator (a, b) c -> Aggregator' fold (TheseTable Expr a b) c -- | Lift an Aggregator1 to operate on a TheseTable. If the -- input query has thoseTable a bs, they are folded into -- a single justTable c by the given aggregator — in the -- case where the input query is all thisTables or -- thatTables, a single nothingTable row is returned. aggregateThoseTable1 :: forall c (fold :: Fold) a b (fold' :: Fold). Table Expr c => Aggregator' fold (a, b) c -> Aggregator' fold' (TheseTable Expr a b) (MaybeTable Expr c) -- | Lift an Aggregator to operate on a TheseTable. If the -- input query has thisTable as or thoseTable -- a _s, the as are folded into a single c by the -- given aggregator — in the case where the input query is all -- thatTables, the Aggregator's fallback c is -- returned. aggregateHereTable :: forall c a (fold :: Fold) b. Table Expr c => Aggregator a c -> Aggregator' fold (TheseTable Expr a b) c -- | Lift an Aggregator1 to operate on an TheseTable. If the -- input query has thisTable as or thoseTable -- a _s, the as are folded into a single -- justTable c by the given aggregator — in the case -- where the input query is all thatTables, a single -- nothingTable row is returned. aggregateHereTable1 :: forall c (fold :: Fold) a (fold' :: Fold) b. Table Expr c => Aggregator' fold a c -> Aggregator' fold' (TheseTable Expr a b) (MaybeTable Expr c) -- | Lift an Aggregator to operate on a TheseTable. If the -- input query has thatTable bs or thoseTable -- _ bs, the bs are folded into a single c by the -- given aggregator — in the case where the input query is all -- thisTables, the Aggregator's fallback c is -- returned. aggregateThereTable :: forall c b (fold :: Fold) a. Table Expr c => Aggregator b c -> Aggregator' fold (TheseTable Expr a b) c -- | Lift an Aggregator1 to operate on an TheseTable. If the -- input query has thatTable bs or thoseTable -- _ bs, the bs are folded into a single -- justTable c by the given aggregator — in the case -- where the input query is all thisTables, a single -- nothingTable row is returned. aggregateThereTable1 :: forall c (fold :: Fold) b (fold' :: Fold) a. Table Expr c => Aggregator' fold b c -> Aggregator' fold' (TheseTable Expr a b) (MaybeTable Expr c) -- | Lift a pair aggregators to operate on a TheseTable. -- thisTables, thatTables are thoseTables are -- grouped separately. aggregateTheseTable :: forall (fold :: Fold) i a (fold' :: Fold) i' b. Aggregator' fold i a -> Aggregator' fold' i' b -> Aggregator1 (TheseTable Expr i i') (TheseTable Expr a b) -- | 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 Name a b -- | A ListTable value contains zero or more instances of -- a. You construct ListTables with many or -- listAgg. data ListTable (context :: Context) a listOf :: Sql DBType a => [Expr a] -> Expr [a] -- | Construct a ListTable from a list of expressions. listTable :: Table Expr a => [a] -> ListTable Expr a -- | Project a single expression out of a ListTable. ($*) :: Projecting a (Expr b) => Projection a (Expr b) -> ListTable Expr a -> Expr [b] infixl 4 $* -- | 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 Name 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 Expr 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 Expr 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 (context :: Context) a nonEmptyOf :: Sql DBType a => NonEmpty (Expr a) -> Expr (NonEmpty a) -- | Construct a NonEmptyTable from a non-empty list of -- expressions. nonEmptyTable :: Table Expr a => NonEmpty a -> NonEmptyTable Expr a -- | Project a single expression out of a NonEmptyTable. ($+) :: Projecting a (Expr b) => Projection a (Expr b) -> NonEmptyTable Expr a -> Expr (NonEmpty b) infixl 4 $+ -- | 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 Name 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 Expr 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 Expr 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) -- | NullTable t is the table t, but where all the -- columns in t have the possibility of being null. This -- is very similar to MaybeTable, 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. data NullTable (context :: Context) a -- | Like nullable. nullableTable :: (Table Expr a, Table Expr b) => b -> (a -> b) -> NullTable Expr a -> b -- | The null table. Like null. nullTable :: Table Expr a => NullTable Expr a -- | Lift any table into NullTable. Like nullify. nullifyTable :: a -> NullTable Expr a -- | Check if any of the non-nullable fields of a are null -- under the NullTable. Returns false if a has no -- non-nullable fields. isNullTable :: Table Expr a => NullTable Expr a -> Expr Bool -- | The inverse of isNullTable. isNonNullTable :: Table Expr a => NullTable Expr a -> Expr Bool -- | Filter a Query that might return nullTable to a -- Query without any nullTables. -- -- Corresponds to catMaybes. catNullTable :: Table Expr a => NullTable Expr a -> Query a -- | Construct a NullTable in the Name context. This can be -- useful if you have a NullTable that you are storing in a table -- and need to construct a TableSchema. nameNullTable :: a -> NullTable Name a -- | Convert a MaybeTable to a NullTable. Note that if the -- underlying a has no non-nullable fields, this is a lossy -- conversion. toNullTable :: Table Expr a => MaybeTable Expr a -> NullTable Expr a -- | Convert a NullTable to a MaybeTable. toMaybeTable :: Table Expr a => NullTable Expr a -> MaybeTable Expr a -- | Assume that a NullTable is non-null. Like -- unsafeUnnullify. unsafeUnnullifyTable :: NullTable Expr a -> a type NameADT (t :: Rel8able) = GGName 'Sum ADTRep t ADT t Name nameADT :: forall (t :: Rel8able). ConstructableADT t => NameADT t data ADT (t :: Rel8able) (context :: Context) class (Generic Record t Result, HTable GColumnsADT t, GSerializeADT TSerialize TColumns Eval ADTRep t Expr Eval ADTRep t Result) => ADTable (t :: Rel8able) type DeconstructADT (t :: Rel8able) r = GGDeconstruct 'Sum ADTRep t ADT t Expr r deconstructADT :: forall (t :: Rel8able) r. (ConstructableADT t, Table Expr r) => DeconstructADT t r type BuildADT (t :: Rel8able) (name :: Symbol) = GGBuild 'Sum name ADTRep t ADT t Expr buildADT :: forall (t :: Rel8able) (name :: Symbol). BuildableADT t name => BuildADT t name type ConstructADT (t :: Rel8able) = forall r. () => GGConstruct 'Sum ADTRep t r constructADT :: forall (t :: Rel8able). ConstructableADT t => ConstructADT t -> ADT t Expr data HKD a (f :: Context) class (Generic Record a, HTable GColumns HKD a, KnownAlgebra GAlgebra Rep a, Eval GGSerialize GAlgebra Rep a TSerialize TColumns Eval HKDRep a Expr Eval HKDRep a Result, GRecord GMap TColumn Result Rep a ~ Rep Record a) => HKDable a type BuildHKD a (name :: Symbol) = GGBuild GAlgebra Rep a name HKDRep a HKD a Expr buildHKD :: forall a (name :: Symbol). BuildableHKD a name => BuildHKD a name type ConstructHKD a = forall r. () => GGConstruct GAlgebra Rep a HKDRep a r constructHKD :: ConstructableHKD a => ConstructHKD a -> HKD a Expr type DeconstructHKD a r = GGDeconstruct GAlgebra Rep a HKDRep a HKD a Expr r deconstructHKD :: (ConstructableHKD a, Table Expr r) => DeconstructHKD a r type NameHKD a = GGName GAlgebra Rep a HKDRep a HKD a Name nameHKD :: ConstructableHKD a => NameHKD a -- | 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 :: QualifiedName -> names -> TableSchema names -- | The name of the table. [name] :: TableSchema names -> QualifiedName -- | The columns of the table. Typically you would use a Rel8able -- data type here, parameterized by the Name context. [columns] :: TableSchema names -> names -- | A 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. data QualifiedName QualifiedName :: String -> Maybe String -> QualifiedName -- | The name of the object. [name] :: QualifiedName -> String -- | The schema that this object belongs to. If Nothing, whatever is -- on the connection's search_path will be used. [schema] :: QualifiedName -> Maybe String -- | 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 :: Type -> 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 -- | Change the type of an Expr, without a cast. Even more unsafe -- than unsafeCastExpr. Only use this if you are certain that the -- typeNames of a and b refer to exactly the -- same PostgreSQL type. unsafeCoerceExpr :: Expr a -> Expr b -- | Unsafely 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! unsafeLiteral :: String -> Expr a -- | Import a raw PrimExpr 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! unsafePrimExpr :: PrimExpr -> 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 -- | Homonullable a b means that both a and b -- can be null, or neither a or b can be -- null. class IsMaybe a ~ IsMaybe b => Homonullable a b -- | 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 -- | Assume 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 -- nullable unless you know what you're doing. unsafeUnnullify :: Expr (Maybe a) -> Expr a -- | 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 ==?. (==.) :: 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 -- /=?. (/=.) :: 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_ :: (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 -- | like x y corresponds to the expression y LIKE x. -- -- Note that the arguments to like are swapped. This is to aid -- currying, so you can write expressions like filter (like "Rel%" . -- packageName) =<< each haskellPackages like :: Expr Text -> Expr Text -> Expr Bool -- | ilike x y corresponds to the expression y ILIKE x. -- -- Note that the arguments to ilike are swapped. This is to aid -- currying, so you can write expressions like filter (ilike "Rel%" . -- packageName) =<< each haskellPackages ilike :: Expr Text -> Expr Text -> Expr Bool -- | 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 -- (<?). (<.) :: 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 -- (<=?). (<=.) :: 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 -- (>?). (>.) :: 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 -- (>=?). (>=.) :: 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 :: 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 :: Sql DBOrd a => Expr a -> Expr a -> Expr a -- | This type class is basically Table Expr, where -- each column of the Table is an argument to the function, but it -- also has an additional instance for () for calling functions -- with no arguments. class Arguments a -- | function name arguments runs the PostgreSQL function -- name with the arguments arguments returning an -- Expr a. function :: (Arguments arguments, Sql DBType a) => QualifiedName -> arguments -> Expr a -- | Construct an expression by applying an infix binary operator to two -- operands. binaryOperator :: Sql DBType c => QualifiedName -> Expr a -> Expr b -> Expr c -- | Select each row from a function that returns a relation. This is -- equivalent to FROM function(input). queryFunction :: (Arguments input, Table Expr output) => QualifiedName -> input -> Query output -- | A less safe version of function that does not wrap the return -- value in a cast. rawFunction :: Arguments arguments => QualifiedName -> arguments -> Expr a -- | A less safe version of binaryOperator that does not wrap the -- return value in a cast. rawBinaryOperator :: QualifiedName -> 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 a SELECT -- statement. showQuery :: Table Expr a => Query a -> String -- | A Projection a bs is a special type of function a -- -> b whereby the resulting b is guaranteed to be -- composed only from columns contained in a. type Projection a b = Transpose Field a a -> Transpose Field a b -- | Projectable f means that f is a kind of -- functor on Tables that allows the mapping of a -- Projection over its underlying columns. class Projectable (f :: Type -> Type) -- | Map a Projection over f. project :: (Projectable f, Projecting a b) => Projection a b -> f a -> f b -- | Biprojectable p means that p is a kind of -- bifunctor on Tables that allows the mapping of a pair of -- Projections over its underlying columns. class Biprojectable (p :: Type -> Type -> Type) -- | Map a pair of Projections over p. biproject :: (Biprojectable p, Projecting a b, Projecting c d) => Projection a b -> Projection c d -> p a c -> p b d -- | The constraint Projecting a b ensures that -- Projection a b is a usable Projection. class (Transposes Context a Field a a Transpose Field a a, Transposes Context a Field a b Transpose Field a b) => Projecting a b -- | A special context used in the construction of Projections. data Field table a -- | Selects a b means that a is a schema (i.e., a -- Table of Names) for the Expr columns in -- b. class Transposes 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. -- present is equivalent to WHERE EXISTS in SQL. present :: Query a -> Query () -- | Produce the empty query if the given query returns rows. -- absent is equivalent to WHERE NOT EXISTS in SQL. absent :: 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 a -- 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 -- a 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 a -- 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 a -- 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 a EXCEPT 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 a 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 <$ present (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 -- | materialize takes a Query and fully evaluates it and -- caches the results thereof, and passes to a continuation a new -- Query 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. -- -- materialize is currently implemented in terms of Postgres' -- @WITH syntax, specifically the WITH _ AS MATERIALIZED -- (_) form introduced in PostgreSQL 12. This means that -- materialize can only be used with PostgreSQL 12 or newer. materialize :: Table Expr a => Query a -> (Query a -> Query b) -> Query b -- | loop allows the construction of recursive queries, using -- Postgres' WITH RECURSIVE under the hood. The first -- argument to loop 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". loop uses UNION ALL to combine the recursive -- and non-recursive terms. -- -- Denotionally, loop s f is the smallest set of rows -- r such that -- --
--   r == s `unionAll` (r >>= f)
--   
-- -- Operationally, loop 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. loop :: Table Expr a => Query a -> (a -> Query a) -> Query a -- | loopDistinct is like loop but uses UNION -- instead of UNION ALL to combine the recursive and -- non-recursive terms. -- -- Denotationally, loopDistinct s f is the smallest set -- of rows r such that -- --
--   r == s `union` (r >>= f)
--   
-- -- Operationally, loopDistinct 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 loopDistinct (in contrast to -- loop). 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. loopDistinct :: Table Expr a => Query a -> (a -> Query a) -> Query a -- | An Aggregator takes a Query producing a collection of -- rows of type a and transforms it into a Query -- producing a single row of type b. If the given Query -- produces an empty collection of rows, then the single row in the -- resulting Query contains the identity values of the aggregation -- functions comprising the Aggregator (i.e., 0 for -- sum, false for or, etc.). -- -- Aggregator is a special form of Aggregator' -- parameterised by Full. type Aggregator = Aggregator' 'Full -- | An Aggregator1 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 BY in -- SQL. If given an empty collection of rows, Aggregator1 will -- have no groups and will therefore also return an empty collection of -- rows. -- -- Aggregator1 is a special form of Aggregator' -- parameterised by Semi. type Aggregator1 = Aggregator' 'Semi -- | Aggregator' is the most general form of "aggregator", of which -- Aggregator and Aggregator1 are special cases. -- Aggregator's are comprised of aggregation functions and/or -- GROUP BY clauses. -- -- Aggregation functions operating on individual Exprs such as -- sum can be combined into Aggregators operating on larger -- types using the Applicative, Profunctor and -- ProductProfunctor interfaces. Working with Profunctors -- can sometimes be awkward so for every sum we also provide a -- sumOn which bundles an lmap. 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
--             }
--   
data Aggregator' (fold :: Fold) i a -- | Fold is a kind that parameterises aggregations. Aggregations -- parameterised by Semi are analogous to foldMap1 (i.e, -- they can only produce results on a non-empty Query) whereas -- aggregations parameterised by Full are analagous to -- foldMap (given a non-empty) query, they return the identity -- values of the aggregation functions. data Fold Semi :: Fold Full :: Fold -- | Given a value to fall back on if given an empty collection of rows, -- toAggregator turns an Aggregator1 into an -- Aggregator. toAggregator :: forall a (fold :: Fold) i (fold' :: Fold). a -> Aggregator' fold i a -> Aggregator' fold' i a -- | toAggregator1 turns an Aggregator into an -- Aggregator1. toAggregator1 :: forall (fold :: Fold) i a. Aggregator' fold i a -> Aggregator1 i a -- | Apply an Aggregator to all rows returned by a Query. If -- the Query is empty, then a single "fallback" row is returned, -- composed of the identity elements of the constituent aggregation -- functions. aggregate :: (Table Expr i, Table Expr a) => Aggregator i a -> Query i -> Query a -- | Apply an Aggregator1 to all rows returned by a Query. If -- the Query is empty, then zero rows are returned. aggregate1 :: forall i (fold :: Fold) a. Table Expr i => Aggregator' fold i a -> Query i -> Query a -- | filterWhere allows an Aggregator to filter out rows from -- the input query before considering them for aggregation. Note that -- because the predicate supplied to filterWhere could return -- false for every row, filterWhere needs an -- Aggregator as opposed to an Aggregator1, so that it can -- return a default value in such a case. For a variant of -- filterWhere that can work with Aggregator1s, see -- filterWhereOptional. filterWhere :: forall a i (fold :: Fold). Table Expr a => (i -> Expr Bool) -> Aggregator i a -> Aggregator' fold i a -- | A variant of filterWhere that can be used with an -- Aggregator1 (upgrading it to an Aggregator in the -- process). It returns nothingTable in the case where the -- predicate matches zero rows. filterWhereOptional :: forall a i (fold :: Fold) (fold' :: Fold). Table Expr a => (i -> Expr Bool) -> Aggregator' fold i a -> Aggregator' fold' i (MaybeTable Expr a) -- | distinctAggregate modifies an Aggregator to consider -- only distinct values of each particular column. Note that this -- "distinction" only happens within each column individually, not across -- all columns simultaneously. distinctAggregate :: forall (fold :: Fold) i a. Aggregator' fold i a -> Aggregator' fold i a -- | Order the values within each aggregation in an Aggregator using -- the given ordering. This is only relevant for aggregations that depend -- on the order they get their elements, like listAgg and -- stringAgg. orderAggregateBy :: forall i (fold :: Fold) a. Order i -> Aggregator' fold i a -> Aggregator' fold i a -- | optionalAggregate upgrades an Aggregator1 into an -- Aggregator by having it return nothingTable when -- aggregating over an empty collection of rows. optionalAggregate :: forall a (fold :: Fold) i (fold' :: Fold). Table Expr a => Aggregator' fold i a -> Aggregator' fold' i (MaybeTable Expr a) -- | 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. -- -- 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
--   
groupBy :: EqTable a => Aggregator1 a a -- | Applies groupBy to the columns selected by the given function. groupByOn :: EqTable a => (i -> a) -> Aggregator1 i a -- | 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 Expr (Item Expr))
--   ordersWithItems = do
--     order <- each orderSchema
--     items <- aggregate listAgg (itemsFromOrder order)
--     return (order, items)
--   
listAgg :: forall a (fold :: Fold). Table Expr a => Aggregator' fold a (ListTable Expr a) -- | Applies listAgg to the columns selected by the given function. listAggOn :: forall a i (fold :: Fold). Table Expr a => (i -> a) -> Aggregator' fold i (ListTable Expr a) -- | Collect expressions values as a list. listAggExpr :: forall a (fold :: Fold). Sql DBType a => Aggregator' fold (Expr a) (Expr [a]) -- | Applies listAggExpr to the column selected by the given -- function. listAggExprOn :: forall a i (fold :: Fold). Sql DBType a => (i -> Expr a) -> Aggregator' fold i (Expr [a]) -- | Concatenate lists into a single list. listCat :: forall a (fold :: Fold). Table Expr a => Aggregator' fold (ListTable Expr a) (ListTable Expr a) -- | Applies listCat to the list selected by the given function. listCatOn :: forall a i (fold :: Fold). Table Expr a => (i -> ListTable Expr a) -> Aggregator' fold i (ListTable Expr a) -- | Concatenate lists into a single list. listCatExpr :: forall a (fold :: Fold). Sql DBType a => Aggregator' fold (Expr [a]) (Expr [a]) -- | Applies listCatExpr to the column selected by the given -- function. listCatExprOn :: forall a i (fold :: Fold). Sql DBType a => (i -> Expr [a]) -> Aggregator' fold i (Expr [a]) -- | Like listAgg, but the result is guaranteed to be a non-empty -- list. nonEmptyAgg :: Table Expr a => Aggregator1 a (NonEmptyTable Expr a) -- | Applies nonEmptyAgg to the columns selected by the given -- function. nonEmptyAggOn :: Table Expr a => (i -> a) -> Aggregator1 i (NonEmptyTable Expr a) -- | Collect expressions values as a non-empty list. nonEmptyAggExpr :: Sql DBType a => Aggregator1 (Expr a) (Expr (NonEmpty a)) -- | Applies nonEmptyAggExpr to the column selected by the given -- function. nonEmptyAggExprOn :: Sql DBType a => (i -> Expr a) -> Aggregator1 i (Expr (NonEmpty a)) -- | Concatenate non-empty lists into a single non-empty list. nonEmptyCat :: Table Expr a => Aggregator1 (NonEmptyTable Expr a) (NonEmptyTable Expr a) -- | Applies nonEmptyCat to the non-empty list selected by the given -- function. nonEmptyCatOn :: Table Expr a => (i -> NonEmptyTable Expr a) -> Aggregator1 i (NonEmptyTable Expr a) -- | Concatenate non-empty lists into a single non-empty list. nonEmptyCatExpr :: Sql DBType a => Aggregator1 (Expr (NonEmpty a)) (Expr (NonEmpty a)) -- | Applies nonEmptyCatExpr to the column selected by the given -- function. nonEmptyCatExprOn :: Sql DBType a => (i -> Expr (NonEmpty a)) -> Aggregator1 i (Expr (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 => Aggregator1 (Expr a) (Expr a) -- | Applies max to the column selected by the given function. maxOn :: Sql DBMax a => (i -> Expr a) -> Aggregator1 i (Expr 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 min -- function. min :: Sql DBMin a => Aggregator1 (Expr a) (Expr a) -- | Applies min to the column selected by the given function. minOn :: Sql DBMin a => (i -> Expr a) -> Aggregator1 i (Expr 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 -- casts back to the original input type. This can lead to overflows, and -- if you anticipate very large sums, you should upcast your input. sum :: forall a (fold :: Fold). (Sql DBNum a, Sql DBSum a) => Aggregator' fold (Expr a) (Expr a) -- | Applies sum to the column selected by the given fucntion. sumOn :: forall a i (fold :: Fold). (Sql DBNum a, Sql DBSum a) => (i -> Expr a) -> Aggregator' fold i (Expr a) -- | sumWhere is a combination of filterWhere and -- sumOn. sumWhere :: forall a i (fold :: Fold). (Sql DBNum a, Sql DBSum a) => (i -> Expr Bool) -> (i -> Expr a) -> Aggregator' fold i (Expr a) -- | Corresponds 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 Double or -- Scientific before calling avg. avg :: Sql DBSum a => Aggregator1 (Expr a) (Expr a) -- | Applies avg to the column selected by the given fucntion. avgOn :: Sql DBSum a => (i -> Expr a) -> Aggregator1 i (Expr a) -- | The class of data types that support the string_agg() -- aggregation function. class DBType a => DBString a -- | Corresponds to string_agg(). stringAgg :: forall a (fold :: Fold). (Sql IsString a, Sql DBString a) => Expr a -> Aggregator' fold (Expr a) (Expr a) -- | Count the occurances of a single column. Corresponds to -- COUNT(a) count :: forall (fold :: Fold) a. Aggregator' fold (Expr a) (Expr Int64) -- | Applies count to the column selected by the given function. countOn :: forall i a (fold :: Fold). (i -> Expr a) -> Aggregator' fold i (Expr Int64) -- | Corresponds to COUNT(*). countStar :: forall (fold :: Fold) i. Aggregator' fold i (Expr Int64) -- | Count the number of distinct occurrences of a single column. -- Corresponds to COUNT(DISTINCT a) countDistinct :: forall a (fold :: Fold). Sql DBEq a => Aggregator' fold (Expr a) (Expr Int64) -- | Applies countDistinct to the column selected by the given -- function. countDistinctOn :: forall a i (fold :: Fold). Sql DBEq a => (i -> Expr a) -> Aggregator' fold i (Expr Int64) -- | A count of the number of times a given expression is true. countWhere :: forall (fold :: Fold). Aggregator' fold (Expr Bool) (Expr Int64) -- | Applies countWhere to the column selected by the given -- function. countWhereOn :: forall i (fold :: Fold). (i -> Expr Bool) -> Aggregator' fold i (Expr Int64) -- | Corresponds to bool_and. and :: forall (fold :: Fold). Aggregator' fold (Expr Bool) (Expr Bool) -- | Applies and to the column selected by the given function. andOn :: forall i (fold :: Fold). (i -> Expr Bool) -> Aggregator' fold i (Expr Bool) -- | Corresponds to bool_or. or :: forall (fold :: Fold). Aggregator' fold (Expr Bool) (Expr Bool) -- | Applies or to the column selected by the given function. orOn :: forall i (fold :: Fold). (i -> Expr Bool) -> Aggregator' fold i (Expr Bool) -- | aggregateFunction allows the use use of custom aggregation -- functions or PostgreSQL aggregation functions which are not otherwise -- supported by Rel8. aggregateFunction :: (Table Expr i, Sql DBType a) => QualifiedName -> Aggregator1 i (Expr a) rawAggregateFunction :: Table Expr i => QualifiedName -> Aggregator1 i (Expr a) -- | Corresponds to mode() WITHIN GROUP (ORDER BY _). mode :: Sql DBOrd a => Aggregator1 (Expr a) (Expr a) -- | Applies mode to the column selected by the given function. modeOn :: Sql DBOrd a => (i -> Expr a) -> Aggregator1 i (Expr a) -- | Corresponds to percentile_disc(_) WITHIN GROUP (ORDER BY _). percentile :: Sql DBOrd a => Expr Double -> Aggregator1 (Expr a) (Expr a) -- | Applies percentile to the column selected by the given -- function. percentileOn :: Sql DBOrd a => Expr Double -> (i -> Expr a) -> Aggregator1 i (Expr a) -- | Corresponds to percentile_cont(_) WITHIN GROUP (ORDER BY _). percentileContinuous :: Sql DBFractional a => Expr Double -> Aggregator1 (Expr a) (Expr a) -- | Applies percentileContinuous to the column selected by the -- given function. percentileContinuousOn :: Sql DBFractional a => Expr Double -> (i -> Expr a) -> Aggregator1 i (Expr a) -- | Corresponds to rank(_) WITHIN GROUP (ORDER BY _). hypotheticalRank :: forall a (fold :: Fold). Order a -> a -> Aggregator' fold a (Expr Int64) -- | Corresponds to dense_rank(_) WITHIN GROUP (ORDER BY _). hypotheticalDenseRank :: forall a (fold :: Fold). Order a -> a -> Aggregator' fold a (Expr Int64) -- | Corresponds to percent_rank(_) WITHIN GROUP (ORDER BY _). hypotheticalPercentRank :: forall a (fold :: Fold). Order a -> a -> Aggregator' fold a (Expr Double) -- | Corresponds to cume_dist(_) WITHIN GROUP (ORDER BY _). hypotheticalCumeDist :: forall a (fold :: Fold). Order a -> a -> Aggregator' fold a (Expr Double) -- | 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 >$< 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 last. This -- corresponds to NULLS LAST in SQL. nullsLast :: Order (Expr a) -> Order (Expr (Maybe a)) -- | Window is an applicative functor that represents expressions -- that contain window functions. window can be used to -- evaluate these expressions over a particular query. data Window a b -- | window runs a query composed of expressions containing -- window functions. window is similar to aggregate, -- with the main difference being that in a window query, each input row -- corresponds to one output row, whereas aggregation queries fold the -- entire input query down into a single row. To put this into a Haskell -- context, aggregate is to foldl as window is to -- scanl. window :: Window a b -> Query a -> Query b -- | In 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 -- Partition represents everything that comes after OVER. -- -- Partition is a Monoid, so Windows created with -- partitionBy and orderWindowBy can be combined using -- <>. data Partition a -- | over adds a Partition to a Window expression. -- --
--   cumulative (sum . salary) over partitionBy department <> orderPartitionBy (salary >$< desc)
--   
over :: Window a b -> Partition a -> Window a b infixl 1 `over` -- | Restricts a window function to operate only the group of rows that -- share the same value(s) for the given expression(s). partitionBy :: EqTable b => (a -> b) -> Partition a -- | Controls the order in which rows are processed by window functions. -- This does not need to match the ordering of the overall query. orderPartitionBy :: Order a -> Partition a -- | cumulative allows the use of aggregation functions in -- Window expressions. In particular, cumulative -- sum (when combined with orderPartitionBy) gives a -- running total, also known as a "cumulative sum", hence the name -- cumulative. cumulative :: forall (fold :: Fold) i a. Aggregator' fold i a -> Window i a -- | Return every column of the current row of a window query. currentRow :: Window a a -- | row_number() rowNumber :: Window i (Expr Int64) -- | rank() rank :: Window i (Expr Int64) -- | dense_rank() denseRank :: Window i (Expr Int64) -- | percent_rank() percentRank :: Window i (Expr Double) -- | cume_dist() cumeDist :: Window i (Expr Double) -- | ntile(num_buckets) ntile :: Expr Int32 -> Window i (Expr Int32) -- | lag n returns the row n rows before the -- current row in a given window. Returns nothingTable if -- n is out of bounds. lag :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a) -- | Applies lag to the columns selected by the given function. lagOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a) -- | lead n returns the row n rows after the -- current row in a given window. Returns nothingTable if -- n is out of bounds. lead :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a) -- | Applies lead to the columns selected by the given function. leadOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a) -- | firstValue returns the first row of the window of the current -- row. firstValue :: Table Expr a => Window a a -- | Applies firstValue to the columns selected by the given -- function. firstValueOn :: Table Expr a => (i -> a) -> Window i a -- | lastValue returns the first row of the window of the current -- row. lastValue :: Table Expr a => Window a a -- | Applies lastValue to the columns selected by the given -- function. lastValueOn :: Table Expr a => (i -> a) -> Window i a -- | nthValue n returns the nth row of the window -- of the current row. Returns nothingTable if n is out -- of bounds. nthValue :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a) -- | Applies nthValue to the columns selected by the given function. nthValueOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a) -- | Pair each row of a query with its index within the query. indexed :: Query a -> Query (Expr Int64, a) -- | rebind 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. rebind :: Table Expr a => String -> a -> Query 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 a normal Haskell type. class Table Expr exprs => ToExprs exprs 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. type Result = Identity -- | Convert a Statement to a runnable Statement, processing -- the result of the statement as a list of rows. -- --
--   run :: Serializable exprs a => Rel8.Statement (Query exprs) -> Hasql.Statement () [a]
--   
run :: Serializable exprs a => Statement (Query exprs) -> Statement () [a] -- | Convert a Statement to a runnable Statement, -- disregarding the results of that statement (if any). -- --
--   run_ :: Rel8.Statement exprs -> Hasql.Statement () ()
--   
run_ :: Statement exprs -> Statement () () -- | Convert a Statement to a runnable Statement, returning -- the number of rows affected by that statement (for inserts, -- updates or Rel8.delete's with NoReturning). -- --
--   runN :: Rel8.Statement () -> Hasql.Statement () Int64
--   
runN :: Statement () -> Statement () Int64 -- | Convert a Statement to a runnable Statement, 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 :: Serializable exprs a => Rel8.Statement (Query exprs) -> Hasql.Statement () a
--   
run1 :: Serializable exprs a => Statement (Query exprs) -> Statement () a -- | Convert a Statement to a runnable Statement, processing -- the result of the statement as Maybe a single row. If the -- statement returns a number of rows other than 0 or 1, a runtime -- exception is thrown. -- --
--   runMaybe :: Serializable exprs a => Rel8.Statement (Query exprs) -> Hasql.Statement () (Maybe a)
--   
runMaybe :: Serializable exprs a => Statement (Query exprs) -> Statement () (Maybe a) -- | Convert a Statement to a runnable Statement, processing -- the result of the statement as a Vector of rows. -- --
--   runVector :: Serializable exprs a => Rel8.Statement (Query exprs) -> Hasql.Statement () (Vector a)
--   
runVector :: Serializable exprs a => Statement (Query exprs) -> Statement () (Vector a) -- | Given a run function that converts a Statement to a -- Statement, return a run-like function which instead -- takes a parameterized Statement and converts it to a -- preparable Statement. -- -- 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 lit. prepared :: forall a b i o. Serializable a i => (Statement b -> Statement () o) -> (a -> Statement b) -> Statement i o -- | Build a SELECT Statement. select :: Table Expr a => Query a -> Statement (Query a) -- | The constituent parts of a SQL INSERT statement. data Insert a [Insert] :: forall names exprs a. Selects names exprs => TableSchema names -> Query exprs -> OnConflict names -> Returning names a -> Insert a -- | OnConflict represents the ON CONFLICT clause of an -- INSERT statement. This specifies what ought to happen when -- one or more of the rows proposed for insertion conflict with an -- existing row in the table. data OnConflict names -- | Abort the transaction if there are conflicting rows (Postgres' -- default) Abort :: OnConflict names -- |
--   ON CONFLICT DO NOTHING
--   
DoNothing :: OnConflict names -- |
--   ON CONFLICT DO UPDATE
--   
DoUpdate :: Upsert names -> OnConflict names -- | The 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. data Upsert names [Upsert] :: forall names exprs index excluded. (Selects names exprs, Projecting names index, excluded ~ exprs) => Projection names index -> Maybe (exprs -> Expr Bool) -> (excluded -> exprs -> exprs) -> (excluded -> exprs -> Expr Bool) -> Upsert names -- | Build an INSERT Statement. insert :: Insert a -> Statement a -- | Corresponds to the SQL DEFAULT expression. -- -- This Expr is unsafe for numerous reasons, and should be used -- with care: -- --
    --
  1. This Expr only makes sense in an INSERT or -- UPDATE statement.
  2. --
  3. Rel8 is not able to verify that a particular column actually has a -- DEFAULT value. Trying to use unsafeDefault where -- there is no default will cause a runtime crash
  4. --
  5. DEFAULT values cannot be transformed. For example, the -- innocuous Rel8 code unsafeDefault + 1 will crash, despite -- type checking.
  6. --
-- -- 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 Insert 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 nextval instead. unsafeDefault :: Expr a -- | Convert an Insert to a String containing an -- INSERT statement. showInsert :: Insert a -> String -- | The constituent parts of a DELETE statement. data Delete a [Delete] :: forall names exprs using a. Selects names exprs => TableSchema names -> Query using -> (using -> exprs -> Expr Bool) -> Returning names a -> Delete a -- | Build a DELETE Statement. delete :: Delete a -> Statement a -- | Convert a Delete to a String containing a -- DELETE statement. showDelete :: Delete a -> String -- | The constituent parts of an UPDATE statement. data Update a [Update] :: forall names exprs from a. Selects names exprs => TableSchema names -> Query from -> (from -> exprs -> exprs) -> (from -> exprs -> Expr Bool) -> Returning names a -> Update a -- | Build an UPDATE Statement. update :: Update a -> Statement a -- | Convert an Update to a String containing an -- UPDATE statement. showUpdate :: Update a -> String -- | Insert, Update and Delete all support an optional -- RETURNING clause. data Returning names a -- | No RETURNING clause [NoReturning] :: forall names. Returning names () -- | Returning 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 nextval). [Returning] :: forall names exprs a1. (Selects names exprs, Table Expr a1) => (exprs -> a1) -> Returning names (Query a1) -- | Statement represents a single PostgreSQL statement. Most -- commonly, this is constructed using select, insert, -- update or delete. -- -- 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. Statement provides a -- Monad instance that captures this "binding" pattern. -- -- The caveat with this is that the side-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, -- unionAlling this with the result of a SELECT 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 = now
--           pure DeletedFoo {..}
--       , onConflict = Abort
--       , returning = NoReturning
--       }
--   
data Statement a -- | Convert a Statement to a String containing an SQL -- statement. showStatement :: Statement a -> String -- | Convert a parameterized Statement to a String containing -- an SQL statement. showPreparedStatement :: Table Expr i => (i -> Statement a) -> String -- | 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 -> Statement () () -- | Given a TableSchema and Query, -- 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. createOrReplaceView :: Selects names exprs => TableSchema names -> Query exprs -> Statement () () -- | See -- https://www.postgresql.org/docs/current/functions-sequence.html nextval :: QualifiedName -> Expr Int64 -- | evaluate takes expressions that could potentially have side -- effects and "runs" them in the Query monad. The returned -- expressions have no side effects and can safely be reused. evaluate :: Table Expr a => a -> Query a module Rel8.Table.Verify -- | getSchemaErrors 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: -- --
    --
  1. for every existing field, the types match
  2. --
  3. all non-nullable columns are present in the hs type
  4. --
  5. no nonexistent columns are present in the hs type
  6. --
  7. no two columns in the same schema share the same name
  8. --
-- -- It'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. getSchemaErrors :: [SomeTableSchema] -> Statement () (Maybe Text) -- | SomeTableSchema 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. data SomeTableSchema [SomeTableSchema] :: forall (k :: (Type -> Type) -> Type). (ToExprs (k Expr) (GFromExprs k), Rel8able k) => TableSchema (k Name) -> SomeTableSchema -- | showCreateTable 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 checkedShowCreateTable showCreateTable :: Rel8able k => TableSchema (k Name) -> String -- | checkedShowCreateTable 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. checkedShowCreateTable :: Rel8able k => TableSchema (k Name) -> Either (Map String (NonEmpty [String])) String instance Rel8.Type.Eq.DBEq Rel8.Table.Verify.Oid instance Rel8.Type.Eq.DBEq Rel8.Table.Verify.Relkind instance Rel8.Type.DBType Rel8.Table.Verify.Oid instance Rel8.Type.DBType Rel8.Table.Verify.Relkind instance GHC.Generics.Generic (Rel8.Table.Verify.Attribute f) instance GHC.Generics.Generic (Rel8.Table.Verify.Cast f) instance GHC.Generics.Generic (Rel8.Table.Verify.PGAttribute f) instance GHC.Generics.Generic (Rel8.Table.Verify.PGCast f) instance GHC.Generics.Generic (Rel8.Table.Verify.PGClass f) instance GHC.Generics.Generic (Rel8.Table.Verify.PGNamespace f) instance GHC.Generics.Generic (Rel8.Table.Verify.PGTable f) instance GHC.Generics.Generic (Rel8.Table.Verify.PGType f) instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.Attribute instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.Cast instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.PGAttribute instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.PGCast instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.PGClass instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.PGNamespace instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.PGTable instance Rel8.Generic.Rel8able.Rel8able Rel8.Table.Verify.PGType instance GHC.Show.Show (Rel8.Table.Verify.Attribute Rel8.Schema.Result.Result) instance GHC.Show.Show (Rel8.Table.Verify.Cast Rel8.Schema.Result.Result) instance GHC.Show.Show Rel8.Table.Verify.CheckEnv instance GHC.Show.Show Rel8.Table.Verify.ColumnError instance GHC.Show.Show Rel8.Table.Verify.ColumnInfo instance GHC.Show.Show Rel8.Table.Verify.Oid instance GHC.Show.Show (Rel8.Table.Verify.PGAttribute Rel8.Schema.Result.Result) instance GHC.Show.Show (Rel8.Table.Verify.PGCast Rel8.Schema.Result.Result) instance GHC.Show.Show (Rel8.Table.Verify.PGClass Rel8.Schema.Result.Result) instance GHC.Show.Show (Rel8.Table.Verify.PGNamespace Rel8.Schema.Result.Result) instance GHC.Show.Show (Rel8.Table.Verify.PGTable Rel8.Schema.Result.Result) instance GHC.Show.Show (Rel8.Table.Verify.PGType Rel8.Schema.Result.Result) instance GHC.Show.Show Rel8.Table.Verify.Relkind instance GHC.Show.Show Rel8.Table.Verify.TableInfo instance GHC.Show.Show Rel8.Table.Verify.TypeInfo