| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Rel8
Synopsis
- class NotNull a => DBType a where
- newtype JSONEncoded a = JSONEncoded {
- fromJSONEncoded :: a
- newtype JSONBEncoded a = JSONBEncoded {
- fromJSONBEncoded :: a
- newtype ReadShow a = ReadShow {
- fromReadShow :: a
- newtype Composite a = Composite a
- class (DBType a, HKDable a) => DBComposite a where
- compose :: DBComposite a => HKD a Expr -> Expr a
- decompose :: forall a. DBComposite a => Expr a -> HKD a Expr
- newtype Enum a = Enum a
- class (DBType a, Enumable a) => DBEnum a where
- enumValue :: a -> String
- enumTypeName :: QualifiedName
- class (Generic a, GEnumable (Rep a)) => Enumable a
- data TypeInformation a = TypeInformation {}
- data TypeName = TypeName {
- name :: QualifiedName
- modifiers :: [String]
- arrayDepth :: Word
- mapTypeInformation :: (a -> b) -> (b -> a) -> TypeInformation a -> TypeInformation b
- parseTypeInformation :: (a -> Either String b) -> (b -> a) -> TypeInformation a -> TypeInformation b
- data Decoder a = Decoder {}
- class DBType a => DBSemigroup a where
- class DBSemigroup a => DBMonoid a where
- memptyExpr :: Expr a
- class DBType a => DBNum a
- class (DBNum a, DBOrd a) => DBIntegral a
- class DBNum a => DBFractional a
- class DBFractional a => DBFloating a
- class HTable (GColumns t) => Rel8able t
- type KRel8able = Rel8able
- type family Column context a where ...
- type family HADT context t where ...
- type family HEither context = either | either -> context where ...
- type family HMaybe context = maybe | maybe -> context where ...
- type family HList context = list | list -> context where ...
- type family HNonEmpty context = nonEmpty | nonEmpty -> context where ...
- type family HNull context = maybe | maybe -> context where ...
- type family HThese context = these | these -> context where ...
- type family Lift context a where ...
- class (HTable (Columns a), context ~ Context a, a ~ Transpose context a) => Table context a | a -> context where
- class HTable t
- class (Table from a, Table to b, Congruent a b, b ~ Transpose to a, a ~ Transpose from b) => Transposes from to a b | a -> from, b -> to, a to -> b, b from -> a
- class AltTable f where
- class AltTable f => AlternativeTable f where
- emptyTable :: Table Expr a => f a
- class Table Expr a => EqTable a where
- (==:) :: forall a. EqTable a => a -> a -> Expr Bool
- (/=:) :: forall a. EqTable a => a -> a -> Expr Bool
- class EqTable a => OrdTable a where
- (<:) :: forall a. OrdTable a => a -> a -> Expr Bool
- (<=:) :: forall a. OrdTable a => a -> a -> Expr Bool
- (>:) :: forall a. OrdTable a => a -> a -> Expr Bool
- (>=:) :: forall a. OrdTable a => a -> a -> Expr Bool
- ascTable :: forall a. OrdTable a => Order a
- descTable :: forall a. OrdTable a => Order a
- greatest :: OrdTable a => a -> a -> a
- least :: OrdTable a => a -> a -> a
- lit :: forall exprs a. Serializable exprs a => a -> exprs
- bool :: Table Expr a => a -> a -> Expr Bool -> a
- case_ :: Table Expr a => [(Expr Bool, a)] -> a -> a
- castTable :: Table Expr a => a -> a
- data MaybeTable context a
- maybeTable :: Table Expr b => b -> (a -> b) -> MaybeTable Expr a -> b
- ($?) :: forall a b. Sql DBType b => (a -> Expr b) -> MaybeTable Expr a -> Expr (Nullify b)
- nothingTable :: Table Expr a => MaybeTable Expr a
- justTable :: a -> MaybeTable Expr a
- isNothingTable :: MaybeTable Expr a -> Expr Bool
- isJustTable :: MaybeTable Expr a -> Expr Bool
- fromMaybeTable :: Table Expr a => a -> MaybeTable Expr a -> a
- optional :: Query a -> Query (MaybeTable Expr a)
- catMaybeTable :: MaybeTable Expr a -> Query a
- traverseMaybeTable :: (a -> Query b) -> MaybeTable Expr a -> Query (MaybeTable Expr b)
- aggregateMaybeTable :: Aggregator' fold i a -> Aggregator1 (MaybeTable Expr i) (MaybeTable Expr a)
- nameMaybeTable :: Name (Maybe MaybeTag) -> a -> MaybeTable Name a
- data EitherTable context a b
- eitherTable :: Table Expr c => (a -> c) -> (b -> c) -> EitherTable Expr a b -> c
- leftTable :: Table Expr b => a -> EitherTable Expr a b
- rightTable :: Table Expr a => b -> EitherTable Expr a b
- isLeftTable :: EitherTable Expr a b -> Expr Bool
- isRightTable :: EitherTable Expr a b -> Expr Bool
- keepLeftTable :: EitherTable Expr a b -> Query a
- keepRightTable :: EitherTable Expr a b -> Query b
- bitraverseEitherTable :: (a -> Query c) -> (b -> Query d) -> EitherTable Expr a b -> Query (EitherTable Expr c d)
- aggregateEitherTable :: Aggregator' fold i a -> Aggregator' fold' i' b -> Aggregator1 (EitherTable Expr i i') (EitherTable Expr a b)
- nameEitherTable :: Name EitherTag -> a -> b -> EitherTable Name a b
- data TheseTable context a b
- theseTable :: Table Expr c => (a -> c) -> (b -> c) -> (a -> b -> c) -> TheseTable Expr a b -> c
- thisTable :: Table Expr b => a -> TheseTable Expr a b
- thatTable :: Table Expr a => b -> TheseTable Expr a b
- thoseTable :: a -> b -> TheseTable Expr a b
- isThisTable :: TheseTable Expr a b -> Expr Bool
- isThatTable :: TheseTable Expr a b -> Expr Bool
- isThoseTable :: TheseTable Expr a b -> Expr Bool
- hasHereTable :: TheseTable Expr a b -> Expr Bool
- hasThereTable :: TheseTable Expr a b -> Expr Bool
- justHereTable :: TheseTable context a b -> MaybeTable context a
- justThereTable :: TheseTable context a b -> MaybeTable context b
- alignMaybeTable :: MaybeTable Expr a -> MaybeTable Expr b -> MaybeTable Expr (TheseTable Expr a b)
- 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)
- aggregateTheseTable :: Aggregator' fold i a -> Aggregator' fold' i' b -> Aggregator1 (TheseTable Expr i i') (TheseTable Expr a b)
- nameTheseTable :: Name (Maybe MaybeTag) -> Name (Maybe MaybeTag) -> a -> b -> TheseTable Name a b
- data ListTable context a
- listTable :: Table Expr a => [a] -> ListTable Expr a
- ($*) :: Projecting a (Expr b) => Projection a (Expr b) -> ListTable Expr a -> Expr [b]
- nameListTable :: Table Name a => a -> ListTable Name a
- many :: Table Expr a => Query a -> Query (ListTable Expr a)
- manyExpr :: Sql DBType a => Query (Expr a) -> Query (Expr [a])
- catListTable :: Table Expr a => ListTable Expr a -> Query a
- catList :: Sql DBType a => Expr [a] -> Query (Expr a)
- data NonEmptyTable context a
- nonEmptyTable :: Table Expr a => NonEmpty a -> NonEmptyTable Expr a
- ($+) :: Projecting a (Expr b) => Projection a (Expr b) -> NonEmptyTable Expr a -> Expr (NonEmpty b)
- nameNonEmptyTable :: Table Name a => a -> NonEmptyTable Name a
- some :: Table Expr a => Query a -> Query (NonEmptyTable Expr a)
- someExpr :: Sql DBType a => Query (Expr a) -> Query (Expr (NonEmpty a))
- catNonEmptyTable :: Table Expr a => NonEmptyTable Expr a -> Query a
- catNonEmpty :: Sql DBType a => Expr (NonEmpty a) -> Query (Expr a)
- data NullTable context a
- nullableTable :: (Table Expr a, Table Expr b) => b -> (a -> b) -> NullTable Expr a -> b
- nullTable :: Table Expr a => NullTable Expr a
- nullifyTable :: a -> NullTable Expr a
- isNullTable :: Table Expr a => NullTable Expr a -> Expr Bool
- isNonNullTable :: Table Expr a => NullTable Expr a -> Expr Bool
- catNullTable :: Table Expr a => NullTable Expr a -> Query a
- nameNullTable :: a -> NullTable Name a
- toNullTable :: Table Expr a => MaybeTable Expr a -> NullTable Expr a
- toMaybeTable :: Table Expr a => NullTable Expr a -> MaybeTable Expr a
- type NameADT t = GGName 'Sum (ADTRep t) (ADT t Name)
- nameADT :: forall t. ConstructableADT t => NameADT t
- data ADT t context
- class (Generic (Record (t Result)), HTable (GColumnsADT t), GSerializeADT TSerialize TColumns (Eval (ADTRep t Expr)) (Eval (ADTRep t Result))) => ADTable t
- type DeconstructADT t r = GGDeconstruct 'Sum (ADTRep t) (ADT t Expr) r
- deconstructADT :: forall t r. (ConstructableADT t, Table Expr r) => DeconstructADT t r
- type BuildADT t name = GGBuild 'Sum name (ADTRep t) (ADT t Expr)
- buildADT :: forall t name. BuildableADT t name => BuildADT t name
- type ConstructADT t = forall r. GGConstruct 'Sum (ADTRep t) r
- constructADT :: forall t. ConstructableADT t => ConstructADT t -> ADT t Expr
- data HKD a f
- 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 = GGBuild (GAlgebra (Rep a)) name (HKDRep a) (HKD a Expr)
- buildHKD :: forall a name. BuildableHKD a name => BuildHKD a name
- type ConstructHKD a = forall r. GGConstruct (GAlgebra (Rep a)) (HKDRep a) r
- constructHKD :: forall a. ConstructableHKD a => ConstructHKD a -> HKD a Expr
- type DeconstructHKD a r = GGDeconstruct (GAlgebra (Rep a)) (HKDRep a) (HKD a Expr) r
- deconstructHKD :: forall a r. (ConstructableHKD a, Table Expr r) => DeconstructHKD a r
- type NameHKD a = GGName (GAlgebra (Rep a)) (HKDRep a) (HKD a Name)
- nameHKD :: forall a. ConstructableHKD a => NameHKD a
- data TableSchema names = TableSchema {
- name :: QualifiedName
- columns :: names
- data QualifiedName = QualifiedName {}
- data Name a
- namesFromLabels :: Table Name a => a
- namesFromLabelsWith :: Table Name a => (NonEmpty String -> String) -> a
- data Expr a
- class (constraint (Unnullify a), Nullable a) => Sql constraint a
- litExpr :: Sql DBType a => a -> Expr a
- unsafeCastExpr :: forall b a. Sql DBType b => Expr a -> Expr b
- unsafeLiteral :: String -> Expr a
- class (Nullable a, IsMaybe a ~ 'False) => NotNull a
- class Nullable' (IsMaybe a) a => Nullable a
- class IsMaybe a ~ IsMaybe b => Homonullable a b
- null :: DBType a => Expr (Maybe a)
- nullify :: NotNull a => Expr a -> Expr (Maybe a)
- nullable :: Table Expr b => b -> (Expr a -> b) -> Expr (Maybe a) -> b
- isNull :: Expr (Maybe a) -> Expr Bool
- isNonNull :: Expr (Maybe a) -> Expr Bool
- mapNull :: DBType b => (Expr a -> Expr b) -> Expr (Maybe a) -> Expr (Maybe b)
- liftOpNull :: DBType c => (Expr a -> Expr b -> Expr c) -> Expr (Maybe a) -> Expr (Maybe b) -> Expr (Maybe c)
- catNull :: Expr (Maybe a) -> Query (Expr a)
- coalesce :: Expr (Maybe Bool) -> Expr Bool
- class DBType a => DBEq a
- true :: Expr Bool
- false :: Expr Bool
- not_ :: Expr Bool -> Expr Bool
- (&&.) :: Expr Bool -> Expr Bool -> Expr Bool
- and_ :: Foldable f => f (Expr Bool) -> Expr Bool
- (||.) :: Expr Bool -> Expr Bool -> Expr Bool
- or_ :: Foldable f => f (Expr Bool) -> Expr Bool
- (==.) :: forall a. Sql DBEq a => Expr a -> Expr a -> Expr Bool
- (/=.) :: forall a. Sql DBEq a => Expr a -> Expr a -> Expr Bool
- (==?) :: DBEq a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool
- (/=?) :: DBEq a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool
- in_ :: forall a f. (Sql DBEq a, Foldable f) => Expr a -> f (Expr a) -> Expr Bool
- boolExpr :: Expr a -> Expr a -> Expr Bool -> Expr a
- caseExpr :: [(Expr Bool, Expr a)] -> Expr a -> Expr a
- like :: Expr Text -> Expr Text -> Expr Bool
- ilike :: Expr Text -> Expr Text -> Expr Bool
- class DBEq a => DBOrd a
- (<.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool
- (<=.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool
- (>.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool
- (>=.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool
- (<?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool
- (<=?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool
- (>?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool
- (>=?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool
- leastExpr :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr a
- greatestExpr :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr a
- class Arguments a
- function :: (Arguments arguments, Sql DBType a) => QualifiedName -> arguments -> Expr a
- binaryOperator :: Sql DBType c => QualifiedName -> Expr a -> Expr b -> Expr c
- queryFunction :: (Arguments input, Table Expr output) => QualifiedName -> input -> Query output
- data Query a
- showQuery :: Table Expr a => Query a -> String
- type Projection a b = Transpose (Field a) a -> Transpose (Field a) b
- class Projectable f where
- project :: Projecting a b => Projection a b -> f a -> f b
- class Biprojectable p where
- biproject :: (Projecting a b, Projecting c d) => Projection a b -> Projection c d -> p a c -> p b d
- class (Transposes (Context a) (Field a) a (Transpose (Field a) a), Transposes (Context a) (Field a) b (Transpose (Field a) b)) => Projecting a b
- data Field table a
- class Transposes Name Expr names exprs => Selects names exprs
- each :: Selects names exprs => TableSchema names -> Query exprs
- values :: (Table Expr a, Foldable f) => f a -> Query a
- filter :: (a -> Expr Bool) -> a -> Query a
- where_ :: Expr Bool -> Query ()
- present :: Query a -> Query ()
- absent :: Query a -> Query ()
- distinct :: EqTable a => Query a -> Query a
- distinctOn :: EqTable b => (a -> b) -> Query a -> Query a
- distinctOnBy :: EqTable b => (a -> b) -> Order a -> Query a -> Query a
- limit :: Word -> Query a -> Query a
- offset :: Word -> Query a -> Query a
- union :: EqTable a => Query a -> Query a -> Query a
- unionAll :: Table Expr a => Query a -> Query a -> Query a
- intersect :: EqTable a => Query a -> Query a -> Query a
- intersectAll :: EqTable a => Query a -> Query a -> Query a
- except :: EqTable a => Query a -> Query a -> Query a
- exceptAll :: EqTable a => Query a -> Query a -> Query a
- exists :: Query a -> Query (Expr Bool)
- with :: (a -> Query b) -> a -> Query a
- withBy :: (a -> b -> Expr Bool) -> Query b -> a -> Query a
- without :: (a -> Query b) -> a -> Query a
- withoutBy :: (a -> b -> Expr Bool) -> Query b -> a -> Query a
- materialize :: (Table Expr a, Table Expr b) => Query a -> (Query a -> Query b) -> Query b
- loop :: Table Expr a => Query a -> (a -> Query a) -> Query a
- loopDistinct :: Table Expr a => Query a -> (a -> Query a) -> Query a
- type Aggregator = Aggregator' 'Full
- type Aggregator1 = Aggregator' 'Semi
- data Aggregator' fold i a
- data Fold
- toAggregator :: a -> Aggregator' fold i a -> Aggregator' fold' i a
- toAggregator1 :: Aggregator' fold i a -> Aggregator1 i a
- aggregate :: (Table Expr i, Table Expr a) => Aggregator i a -> Query i -> Query a
- aggregate1 :: Table Expr i => Aggregator' fold i a -> Query i -> Query a
- filterWhere :: Table Expr a => (i -> Expr Bool) -> Aggregator i a -> Aggregator' fold i a
- filterWhereOptional :: Table Expr a => (i -> Expr Bool) -> Aggregator' fold i a -> Aggregator' fold' i (MaybeTable Expr a)
- distinctAggregate :: Aggregator' fold i a -> Aggregator' fold i a
- orderAggregateBy :: Order i -> Aggregator' fold i a -> Aggregator' fold i a
- optionalAggregate :: Table Expr a => Aggregator' fold i a -> Aggregator' fold' i (MaybeTable Expr a)
- countRows :: Query a -> Query (Expr Int64)
- groupBy :: forall a. EqTable a => Aggregator1 a a
- groupByOn :: EqTable a => (i -> a) -> Aggregator1 i a
- listAgg :: Table Expr a => Aggregator' fold a (ListTable Expr a)
- listAggOn :: Table Expr a => (i -> a) -> Aggregator' fold i (ListTable Expr a)
- listAggExpr :: Sql DBType a => Aggregator' fold (Expr a) (Expr [a])
- listAggExprOn :: Sql DBType a => (i -> Expr a) -> Aggregator' fold i (Expr [a])
- listCat :: Table Expr a => Aggregator' fold (ListTable Expr a) (ListTable Expr a)
- listCatOn :: Table Expr a => (i -> ListTable Expr a) -> Aggregator' fold i (ListTable Expr a)
- listCatExpr :: Sql DBType a => Aggregator' fold (Expr [a]) (Expr [a])
- listCatExprOn :: Sql DBType a => (i -> Expr [a]) -> Aggregator' fold i (Expr [a])
- nonEmptyAgg :: Table Expr a => Aggregator1 a (NonEmptyTable Expr a)
- nonEmptyAggOn :: Table Expr a => (i -> a) -> Aggregator1 i (NonEmptyTable Expr a)
- nonEmptyAggExpr :: Sql DBType a => Aggregator1 (Expr a) (Expr (NonEmpty a))
- nonEmptyAggExprOn :: Sql DBType a => (i -> Expr a) -> Aggregator1 i (Expr (NonEmpty a))
- nonEmptyCat :: Table Expr a => Aggregator1 (NonEmptyTable Expr a) (NonEmptyTable Expr a)
- nonEmptyCatOn :: Table Expr a => (i -> NonEmptyTable Expr a) -> Aggregator1 i (NonEmptyTable Expr a)
- nonEmptyCatExpr :: Sql DBType a => Aggregator1 (Expr (NonEmpty a)) (Expr (NonEmpty a))
- nonEmptyCatExprOn :: Sql DBType a => (i -> Expr (NonEmpty a)) -> Aggregator1 i (Expr (NonEmpty a))
- class DBOrd a => DBMax a
- max :: Sql DBMax a => Aggregator1 (Expr a) (Expr a)
- maxOn :: Sql DBMax a => (i -> Expr a) -> Aggregator1 i (Expr a)
- class DBOrd a => DBMin a
- min :: Sql DBMin a => Aggregator1 (Expr a) (Expr a)
- minOn :: Sql DBMin a => (i -> Expr a) -> Aggregator1 i (Expr a)
- class DBType a => DBSum a
- sum :: (Sql DBNum a, Sql DBSum a) => Aggregator' fold (Expr a) (Expr a)
- sumOn :: (Sql DBNum a, Sql DBSum a) => (i -> Expr a) -> Aggregator' fold i (Expr a)
- sumWhere :: (Sql DBNum a, Sql DBSum a) => (i -> Expr Bool) -> (i -> Expr a) -> Aggregator' fold i (Expr a)
- avg :: Sql DBSum a => Aggregator1 (Expr a) (Expr a)
- avgOn :: Sql DBSum a => (i -> Expr a) -> Aggregator1 i (Expr a)
- class DBType a => DBString a
- stringAgg :: (Sql IsString a, Sql DBString a) => Expr a -> Aggregator' fold (Expr a) (Expr a)
- count :: Aggregator' fold (Expr a) (Expr Int64)
- countOn :: (i -> Expr a) -> Aggregator' fold i (Expr Int64)
- countStar :: Aggregator' fold i (Expr Int64)
- countDistinct :: Sql DBEq a => Aggregator' fold (Expr a) (Expr Int64)
- countDistinctOn :: Sql DBEq a => (i -> Expr a) -> Aggregator' fold i (Expr Int64)
- countWhere :: Aggregator' fold (Expr Bool) (Expr Int64)
- countWhereOn :: (i -> Expr Bool) -> Aggregator' fold i (Expr Int64)
- and :: Aggregator' fold (Expr Bool) (Expr Bool)
- andOn :: (i -> Expr Bool) -> Aggregator' fold i (Expr Bool)
- or :: Aggregator' fold (Expr Bool) (Expr Bool)
- orOn :: (i -> Expr Bool) -> Aggregator' fold i (Expr Bool)
- aggregateFunction :: (Table Expr i, Sql DBType a) => QualifiedName -> Aggregator1 i (Expr a)
- mode :: Sql DBOrd a => Aggregator1 (Expr a) (Expr a)
- modeOn :: Sql DBOrd a => (i -> Expr a) -> Aggregator1 i (Expr a)
- percentile :: Sql DBOrd a => Expr Double -> Aggregator1 (Expr a) (Expr a)
- percentileOn :: Sql DBOrd a => Expr Double -> (i -> Expr a) -> Aggregator1 i (Expr a)
- percentileContinuous :: Sql DBFractional a => Expr Double -> Aggregator1 (Expr a) (Expr a)
- percentileContinuousOn :: Sql DBFractional a => Expr Double -> (i -> Expr a) -> Aggregator1 i (Expr a)
- hypotheticalRank :: Order a -> a -> Aggregator' fold a (Expr Int64)
- hypotheticalDenseRank :: Order a -> a -> Aggregator' fold a (Expr Int64)
- hypotheticalPercentRank :: Order a -> a -> Aggregator' fold a (Expr Double)
- hypotheticalCumeDist :: Order a -> a -> Aggregator' fold a (Expr Double)
- orderBy :: Order a -> Query a -> Query a
- data Order a
- asc :: DBOrd a => Order (Expr a)
- desc :: DBOrd a => Order (Expr a)
- nullsFirst :: Order (Expr a) -> Order (Expr (Maybe a))
- nullsLast :: Order (Expr a) -> Order (Expr (Maybe a))
- data Window a b
- window :: Window a b -> Query a -> Query b
- data Partition a
- over :: Window a b -> Partition a -> Window a b
- partitionBy :: forall b a. EqTable b => (a -> b) -> Partition a
- orderPartitionBy :: Order a -> Partition a
- cumulative :: Aggregator' fold i a -> Window i a
- currentRow :: Window a a
- rowNumber :: Window i (Expr Int64)
- rank :: Window i (Expr Int64)
- denseRank :: Window i (Expr Int64)
- percentRank :: Window i (Expr Double)
- cumeDist :: Window i (Expr Double)
- ntile :: Expr Int32 -> Window i (Expr Int32)
- lag :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a)
- lagOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a)
- lead :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a)
- leadOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a)
- firstValue :: Table Expr a => Window a a
- firstValueOn :: Table Expr a => (i -> a) -> Window i a
- lastValue :: Table Expr a => Window a a
- lastValueOn :: Table Expr a => (i -> a) -> Window i a
- nthValue :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a)
- nthValueOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a)
- indexed :: Query a -> Query (Expr Int64, a)
- rebind :: Table Expr a => String -> a -> Query a
- class (ToExprs exprs a, a ~ FromExprs exprs) => Serializable exprs a | exprs -> a
- class Table Expr exprs => ToExprs exprs a
- type Result = Identity
- run :: Serializable exprs a => Statement (Query exprs) -> Statement () [a]
- run_ :: Statement exprs -> Statement () ()
- runN :: Statement () -> Statement () Int64
- run1 :: Serializable exprs a => Statement (Query exprs) -> Statement () a
- runMaybe :: Serializable exprs a => Statement (Query exprs) -> Statement () (Maybe a)
- runVector :: Serializable exprs a => Statement (Query exprs) -> Statement () (Vector a)
- select :: Table Expr a => Query a -> Statement (Query a)
- data Insert a where
- data OnConflict names
- data Upsert names where
- Upsert :: (Selects names exprs, Projecting names index, excluded ~ exprs) => {..} -> Upsert names
- insert :: Insert a -> Statement a
- unsafeDefault :: Expr a
- showInsert :: Insert a -> String
- data Delete a where
- delete :: Delete a -> Statement a
- showDelete :: Delete a -> String
- data Update a where
- update :: Update a -> Statement a
- showUpdate :: Update a -> String
- data Returning names a where
- data Statement a
- showStatement :: Statement a -> String
- createView :: Selects names exprs => TableSchema names -> Query exprs -> Statement () ()
- createOrReplaceView :: Selects names exprs => TableSchema names -> Query exprs -> Statement () ()
- nextval :: QualifiedName -> Expr Int64
- evaluate :: Table Expr a => a -> Query a
Database types
DBType
class NotNull a => DBType a where Source #
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.
Methods
Instances
| DBType Value Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Int16 Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Int32 Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Int64 Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType ByteString Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType ByteString Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Scientific Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Text Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Text Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Day Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType UTCTime Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType CalendarDiffTime Source # | Corresponds to |
Defined in Rel8.Type Methods typeInformation :: TypeInformation CalendarDiffTime Source # | |
| DBType LocalTime Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType TimeOfDay Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType UUID Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Bool Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Char Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Double Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType Float Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| Sql DBType a => DBType (NonEmpty a) Source # | |
Defined in Rel8.Type Methods | |
| DBType (CI Text) Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType (CI Text) Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBType (NetAddr IP) Source # | Corresponds to |
Defined in Rel8.Type Methods | |
| DBComposite a => DBType (Composite a) Source # | |
Defined in Rel8.Type.Composite Methods | |
| DBEnum a => DBType (Enum a) Source # | |
Defined in Rel8.Type.Enum Methods typeInformation :: TypeInformation (Enum a) Source # | |
| (FromJSON a, ToJSON a) => DBType (JSONBEncoded a) Source # | |
Defined in Rel8.Type.JSONBEncoded Methods typeInformation :: TypeInformation (JSONBEncoded a) Source # | |
| (FromJSON a, ToJSON a) => DBType (JSONEncoded a) Source # | |
Defined in Rel8.Type.JSONEncoded Methods | |
| (Read a, Show a, Typeable a) => DBType (ReadShow a) Source # | |
Defined in Rel8.Type.ReadShow Methods | |
| Sql DBType a => DBType [a] Source # | |
Defined in Rel8.Type Methods typeInformation :: TypeInformation [a] Source # | |
| PowerOf10 n => DBType (Fixed n) Source # | Corresponds to |
Defined in Rel8.Type Methods typeInformation :: TypeInformation (Fixed n) Source # | |
Deriving-via helpers
JSONEncoded
newtype JSONEncoded a Source #
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.
Constructors
| JSONEncoded | |
Fields
| |
Instances
| (FromJSON a, ToJSON a) => DBType (JSONEncoded a) Source # | |
Defined in Rel8.Type.JSONEncoded Methods | |
newtype JSONBEncoded a Source #
Like JSONEncoded, but works for jsonb columns.
Constructors
| JSONBEncoded | |
Fields
| |
Instances
| (FromJSON a, ToJSON a) => DBType (JSONBEncoded a) Source # | |
Defined in Rel8.Type.JSONBEncoded Methods typeInformation :: TypeInformation (JSONBEncoded a) Source # | |
ReadShow
A deriving-via helper type for column types that store a Haskell value
using a Haskell's Read and Show type classes.
Constructors
| ReadShow | |
Fields
| |
Generic
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).
Constructors
| Composite a |
Instances
| DBComposite a => DBType (Composite a) Source # | |
Defined in Rel8.Type.Composite Methods | |
| (DBComposite a, EqTable (HKD a Expr)) => DBEq (Composite a) Source # | |
Defined in Rel8.Type.Composite | |
| (DBComposite a, OrdTable (HKD a Expr)) => DBMax (Composite a) Source # | |
Defined in Rel8.Type.Composite | |
| (DBComposite a, OrdTable (HKD a Expr)) => DBMin (Composite a) Source # | |
Defined in Rel8.Type.Composite | |
| (DBComposite a, OrdTable (HKD a Expr)) => DBOrd (Composite a) Source # | |
Defined in Rel8.Type.Composite | |
class (DBType a, HKDable a) => DBComposite a where Source #
DBComposite is used to associate composite type metadata with a Haskell
type.
Methods
compositeFields :: HKD a Name Source #
The names of all fields in the composite type that a maps to.
compositeTypeName :: QualifiedName Source #
The name of the composite type that a maps to.
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).
Constructors
| Enum a |
Instances
| DBEnum a => DBType (Enum a) Source # | |
Defined in Rel8.Type.Enum Methods typeInformation :: TypeInformation (Enum a) Source # | |
| DBEnum a => DBEq (Enum a) Source # | |
Defined in Rel8.Type.Enum | |
| DBEnum a => DBMax (Enum a) Source # | |
Defined in Rel8.Type.Enum | |
| DBEnum a => DBMin (Enum a) Source # | |
Defined in Rel8.Type.Enum | |
| DBEnum a => DBOrd (Enum a) Source # | |
Defined in Rel8.Type.Enum | |
class (DBType a, Enumable a) => DBEnum a where Source #
DBEnum contains the necessary metadata to describe a PostgreSQL enum type.
Minimal complete definition
Methods
enumValue :: a -> String Source #
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.
enumTypeName :: QualifiedName Source #
The name of the PostgreSQL enum type that a maps to.
class (Generic a, GEnumable (Rep a)) => Enumable a Source #
Types that are sum types, where each constructor is unary (that is, has no fields).
TypeInformation
data TypeInformation a Source #
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.
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.
Constructors
| TypeName | |
Fields
| |
Instances
| IsString TypeName Source # | Constructs |
Defined in Rel8.Type.Name Methods fromString :: String -> TypeName # | |
mapTypeInformation :: (a -> b) -> (b -> a) -> TypeInformation a -> TypeInformation b Source #
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.
parseTypeInformation :: (a -> Either String b) -> (b -> a) -> TypeInformation a -> TypeInformation b Source #
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.
Decoder
Constructors
| Decoder | |
The DBType hierarchy
class DBType a => DBSemigroup a where Source #
The class of DBTypes that form a semigroup. This class is purely a
Rel8 concept, and exists to mirror the Semigroup class.
Instances
| DBSemigroup ByteString Source # | |
Defined in Rel8.Type.Semigroup Methods (<>.) :: Expr ByteString -> Expr ByteString -> Expr ByteString Source # | |
| DBSemigroup ByteString Source # | |
Defined in Rel8.Type.Semigroup Methods (<>.) :: Expr ByteString -> Expr ByteString -> Expr ByteString Source # | |
| DBSemigroup Text Source # | |
| DBSemigroup Text Source # | |
| DBSemigroup CalendarDiffTime Source # | |
Defined in Rel8.Type.Semigroup Methods (<>.) :: Expr CalendarDiffTime -> Expr CalendarDiffTime -> Expr CalendarDiffTime Source # | |
| Sql DBType a => DBSemigroup (NonEmpty a) Source # | |
| DBSemigroup (CI Text) Source # | |
| DBSemigroup (CI Text) Source # | |
| Sql DBType a => DBSemigroup [a] Source # | |
class DBSemigroup a => DBMonoid a where Source #
The class of DBTypes that form a semigroup. This class is purely a
Rel8 concept, and exists to mirror the Monoid class.
Methods
memptyExpr :: Expr a Source #
Instances
| DBMonoid ByteString Source # | |
Defined in Rel8.Type.Monoid Methods | |
| DBMonoid ByteString Source # | |
Defined in Rel8.Type.Monoid Methods | |
| DBMonoid Text Source # | |
Defined in Rel8.Type.Monoid Methods memptyExpr :: Expr Text Source # | |
| DBMonoid Text Source # | |
Defined in Rel8.Type.Monoid Methods memptyExpr :: Expr Text Source # | |
| DBMonoid CalendarDiffTime Source # | |
Defined in Rel8.Type.Monoid Methods | |
| DBMonoid (CI Text) Source # | |
Defined in Rel8.Type.Monoid | |
| DBMonoid (CI Text) Source # | |
Defined in Rel8.Type.Monoid | |
| Sql DBType a => DBMonoid [a] Source # | |
Defined in Rel8.Type.Monoid Methods memptyExpr :: Expr [a] Source # | |
class DBType a => DBNum a Source #
The class of database types that support the +, *, - operators, and
the abs, negate, sign functions.
Instances
| DBNum Int16 Source # | |
Defined in Rel8.Type.Num | |
| DBNum Int32 Source # | |
Defined in Rel8.Type.Num | |
| DBNum Int64 Source # | |
Defined in Rel8.Type.Num | |
| DBNum Scientific Source # | |
Defined in Rel8.Type.Num | |
| DBNum Double Source # | |
Defined in Rel8.Type.Num | |
| DBNum Float Source # | |
Defined in Rel8.Type.Num | |
| PowerOf10 n => DBNum (Fixed n) Source # | |
Defined in Rel8.Type.Num | |
class (DBNum a, DBOrd a) => DBIntegral a Source #
The class of database types that can be coerced to from integral
expressions. This is a Rel8 concept, and allows us to provide
fromIntegral.
Instances
| DBIntegral Int16 Source # | |
Defined in Rel8.Type.Num | |
| DBIntegral Int32 Source # | |
Defined in Rel8.Type.Num | |
| DBIntegral Int64 Source # | |
Defined in Rel8.Type.Num | |
class DBNum a => DBFractional a Source #
The class of database types that support the / operator.
Instances
| DBFractional Scientific Source # | |
Defined in Rel8.Type.Num | |
| DBFractional Double Source # | |
Defined in Rel8.Type.Num | |
| DBFractional Float Source # | |
Defined in Rel8.Type.Num | |
| PowerOf10 n => DBFractional (Fixed n) Source # | |
Defined in Rel8.Type.Num | |
class DBFractional a => DBFloating a Source #
The class of database types that support the / operator.
Instances
| DBFloating Double Source # | |
Defined in Rel8.Type.Num | |
| DBFloating Float Source # | |
Defined in Rel8.Type.Num | |
Tables and higher-kinded tables
class HTable (GColumns t) => Rel8able t Source #
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:
- Nested
data Nested f =
Nested { nested1 :: MyType f
, nested2 :: MyType f
}
The Rel8able type class is used to give us a special mapping operation
that lets us change the type parameter f.
- Supplying
Rel8ableinstances
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 )
Instances
| ADTable t => Rel8able (ADT t) Source # | |
Defined in Rel8.Table.ADT Methods gfromColumns :: forall (context :: Context). SContext context -> GColumns (ADT t) context -> ADT t context gtoColumns :: forall (context :: Context). SContext context -> ADT t context -> GColumns (ADT t) context gfromResult :: GColumns (ADT t) Result -> GFromExprs (ADT t) | |
| HKDable a => Rel8able (HKD a) Source # | |
Defined in Rel8.Table.HKD Methods gfromColumns :: forall (context :: Context). SContext context -> GColumns (HKD a) context -> HKD a context gtoColumns :: forall (context :: Context). SContext context -> HKD a context -> GColumns (HKD a) context gfromResult :: GColumns (HKD a) Result -> GFromExprs (HKD a) | |
type family Column context a where ... Source #
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 HEither context = either | either -> context where ... Source #
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.
Equations
| HEither Result = Either | |
| HEither context = EitherTable context |
type family HMaybe context = maybe | maybe -> context where ... Source #
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.
Equations
| HMaybe Result = Maybe | |
| HMaybe context = MaybeTable context |
type family HList context = list | list -> context where ... Source #
type family HNonEmpty context = nonEmpty | nonEmpty -> context where ... Source #
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.
Equations
| HNonEmpty Result = NonEmpty | |
| HNonEmpty context = NonEmptyTable context |
type family HNull context = maybe | maybe -> context where ... Source #
type family HThese context = these | these -> context where ... Source #
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.
Equations
| HThese Result = These | |
| HThese context = TheseTable context |
class (HTable (Columns a), context ~ Context a, a ~ Transpose context a) => Table context a | a -> context where Source #
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.
Minimal complete definition
Nothing
Associated Types
type Columns a :: HTable Source #
The HTable functor that describes the schema of this table.
type Context a :: Context Source #
The common context that all columns use as an interpretation.
type FromExprs a :: Type Source #
The FromExprs type family maps a type in the Expr context to the
corresponding Haskell type.
type FromExprs a = Map TFromExprs a
type Transpose (context' :: Context) a :: Type Source #
type Transpose context a = Map (TTranspose context) a
Methods
toColumns :: a -> Columns a context Source #
default toColumns :: (Generic (Record a), GTable (TTable context) TColumns (Rep (Record a)), Columns a ~ GColumns TColumns (Rep (Record a))) => a -> Columns a context Source #
fromColumns :: Columns a context -> a Source #
default fromColumns :: (Generic (Record a), GTable (TTable context) TColumns (Rep (Record a)), Columns a ~ GColumns TColumns (Rep (Record a))) => Columns a context -> a Source #
Instances
| Sql DBType a => Table Expr (Expr a) Source # | |
| Sql DBType a => Table Name (Name a) Source # | |
| Sql DBType a => Table Result (Identity a) Source # | |
| (Rel8able t, Reifiable context, context ~ context') => Table context' (t context) Source # | |
| (Table context a, Table context b) => Table context (a, b) Source # | |
| (Table context a, context ~ context') => Table context' (ListTable context a) Source # | |
Defined in Rel8.Table.List Associated Types type Columns (ListTable context a) :: HTable Source # type Context (ListTable context a) :: Context Source # Methods toColumns :: ListTable context a -> Columns (ListTable context a) context' Source # fromColumns :: Columns (ListTable context a) context' -> ListTable context a Source # fromResult :: Columns (ListTable context a) Result -> FromExprs (ListTable context a) Source # toResult :: FromExprs (ListTable context a) -> Columns (ListTable context a) Result Source # | |
| (Table context a, Reifiable context, context ~ context') => Table context' (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe Associated Types type Columns (MaybeTable context a) :: HTable Source # type Context (MaybeTable context a) :: Context Source # type FromExprs (MaybeTable context a) Source # type Transpose context' (MaybeTable context a) Source # Methods toColumns :: MaybeTable context a -> Columns (MaybeTable context a) context' Source # fromColumns :: Columns (MaybeTable context a) context' -> MaybeTable context a Source # fromResult :: Columns (MaybeTable context a) Result -> FromExprs (MaybeTable context a) Source # toResult :: FromExprs (MaybeTable context a) -> Columns (MaybeTable context a) Result Source # | |
| (Table context a, context ~ context') => Table context' (NonEmptyTable context a) Source # | |
Defined in Rel8.Table.NonEmpty Associated Types type Columns (NonEmptyTable context a) :: HTable Source # type Context (NonEmptyTable context a) :: Context Source # type FromExprs (NonEmptyTable context a) Source # type Transpose context' (NonEmptyTable context a) Source # Methods toColumns :: NonEmptyTable context a -> Columns (NonEmptyTable context a) context' Source # fromColumns :: Columns (NonEmptyTable context a) context' -> NonEmptyTable context a Source # fromResult :: Columns (NonEmptyTable context a) Result -> FromExprs (NonEmptyTable context a) Source # toResult :: FromExprs (NonEmptyTable context a) -> Columns (NonEmptyTable context a) Result Source # | |
| (Table context a, Reifiable context, context ~ context') => Table context' (NullTable context a) Source # | |
Defined in Rel8.Table.Null Associated Types type Columns (NullTable context a) :: HTable Source # type Context (NullTable context a) :: Context Source # Methods toColumns :: NullTable context a -> Columns (NullTable context a) context' Source # fromColumns :: Columns (NullTable context a) context' -> NullTable context a Source # fromResult :: Columns (NullTable context a) Result -> FromExprs (NullTable context a) Source # toResult :: FromExprs (NullTable context a) -> Columns (NullTable context a) Result Source # | |
| (Table context a, Table context b, Table context c) => Table context (a, b, c) Source # | |
| (Table context a, Table context b, Reifiable context, context ~ context') => Table context' (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either Associated Types type Columns (EitherTable context a b) :: HTable Source # type Context (EitherTable context a b) :: Context Source # type FromExprs (EitherTable context a b) Source # type Transpose context' (EitherTable context a b) Source # Methods toColumns :: EitherTable context a b -> Columns (EitherTable context a b) context' Source # fromColumns :: Columns (EitherTable context a b) context' -> EitherTable context a b Source # fromResult :: Columns (EitherTable context a b) Result -> FromExprs (EitherTable context a b) Source # toResult :: FromExprs (EitherTable context a b) -> Columns (EitherTable context a b) Result Source # | |
| (Table context a, Table context b, Reifiable context, context ~ context') => Table context' (TheseTable context a b) Source # | |
Defined in Rel8.Table.These Associated Types type Columns (TheseTable context a b) :: HTable Source # type Context (TheseTable context a b) :: Context Source # type FromExprs (TheseTable context a b) Source # type Transpose context' (TheseTable context a b) Source # Methods toColumns :: TheseTable context a b -> Columns (TheseTable context a b) context' Source # fromColumns :: Columns (TheseTable context a b) context' -> TheseTable context a b Source # fromResult :: Columns (TheseTable context a b) Result -> FromExprs (TheseTable context a b) Source # toResult :: FromExprs (TheseTable context a b) -> Columns (TheseTable context a b) Result Source # | |
| (Table context a, Table context b, Table context c, Table context d) => Table context (a, b, c, d) Source # | |
| (Table context a, Table context b, Table context c, Table context d, Table context e) => Table context (a, b, c, d, e) Source # | |
Defined in Rel8.Table Associated Types type Columns (a, b, c, d, e) :: HTable Source # type Context (a, b, c, d, e) :: Context Source # Methods toColumns :: (a, b, c, d, e) -> Columns (a, b, c, d, e) context Source # fromColumns :: Columns (a, b, c, d, e) context -> (a, b, c, d, e) Source # fromResult :: Columns (a, b, c, d, e) Result -> FromExprs (a, b, c, d, e) Source # toResult :: FromExprs (a, b, c, d, e) -> Columns (a, b, c, d, e) Result Source # | |
| (Table context a, Table context b, Table context c, Table context d, Table context e, Table context f) => Table context (a, b, c, d, e, f) Source # | |
Defined in Rel8.Table Associated Types type Columns (a, b, c, d, e, f) :: HTable Source # type Context (a, b, c, d, e, f) :: Context Source # Methods toColumns :: (a, b, c, d, e, f) -> Columns (a, b, c, d, e, f) context Source # fromColumns :: Columns (a, b, c, d, e, f) context -> (a, b, c, d, e, f) Source # fromResult :: Columns (a, b, c, d, e, f) Result -> FromExprs (a, b, c, d, e, f) Source # toResult :: FromExprs (a, b, c, d, e, f) -> Columns (a, b, c, d, e, f) Result Source # | |
| (Table context a, Table context b, Table context c, Table context d, Table context e, Table context f, Table context g) => Table context (a, b, c, d, e, f, g) Source # | |
Defined in Rel8.Table Associated Types type Columns (a, b, c, d, e, f, g) :: HTable Source # type Context (a, b, c, d, e, f, g) :: Context Source # Methods toColumns :: (a, b, c, d, e, f, g) -> Columns (a, b, c, d, e, f, g) context Source # fromColumns :: Columns (a, b, c, d, e, f, g) context -> (a, b, c, d, e, f, g) Source # fromResult :: Columns (a, b, c, d, e, f, g) Result -> FromExprs (a, b, c, d, e, f, g) Source # toResult :: FromExprs (a, b, c, d, e, f, g) -> Columns (a, b, c, d, e, f, g) Result Source # | |
| Sql DBType a => Table (Field table) (Field table a) Source # | |
Defined in Rel8.Schema.Field Associated Types type Columns (Field table a) :: HTable Source # type Context (Field table a) :: Context Source # Methods toColumns :: Field table a -> Columns (Field table a) (Field table) Source # fromColumns :: Columns (Field table a) (Field table) -> Field table a Source # fromResult :: Columns (Field table a) Result -> FromExprs (Field table a) Source # toResult :: FromExprs (Field table a) -> Columns (Field table a) Result Source # | |
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 (Table from a, Table to b, Congruent a b, b ~ Transpose to a, a ~ Transpose from b) => Transposes from to a b | a -> from, b -> to, a to -> b, b from -> a Source #
means that Transposes from to a ba 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).
Instances
| (Table from a, Table to b, Congruent a b, b ~ Transpose to a, a ~ Transpose from b) => Transposes from to a b Source # | |
Defined in Rel8.Table.Transpose | |
class AltTable f where Source #
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.
Methods
(<|>:) :: Table Expr a => f a -> f a -> f a infixl 3 Source #
An associative binary operation on Tables.
Instances
| AltTable Query Source # | |
| context ~ Expr => AltTable (ListTable context) Source # | |
| context ~ Expr => AltTable (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods (<|>:) :: Table Expr a => MaybeTable context a -> MaybeTable context a -> MaybeTable context a Source # | |
| context ~ Expr => AltTable (NonEmptyTable context) Source # | |
Defined in Rel8.Table.NonEmpty Methods (<|>:) :: Table Expr a => NonEmptyTable context a -> NonEmptyTable context a -> NonEmptyTable context a Source # | |
| context ~ Expr => AltTable (NullTable context) Source # | |
| EqTable k => AltTable (Tabulation k) Source # | If |
Defined in Rel8.Tabulate Methods (<|>:) :: Table Expr a => Tabulation k a -> Tabulation k a -> Tabulation k a Source # | |
class AltTable f => AlternativeTable f where Source #
Like Alternative in Haskell, some Tables form a monoid on applicative
functors.
Instances
| AlternativeTable Query Source # |
|
Defined in Rel8.Query | |
| context ~ Expr => AlternativeTable (ListTable context) Source # | |
Defined in Rel8.Table.List | |
| context ~ Expr => AlternativeTable (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods emptyTable :: Table Expr a => MaybeTable context a Source # | |
| context ~ Expr => AlternativeTable (NullTable context) Source # | |
Defined in Rel8.Table.Null | |
| EqTable k => AlternativeTable (Tabulation k) Source # | |
Defined in Rel8.Tabulate Methods emptyTable :: Table Expr a => Tabulation k a Source # | |
class Table Expr a => EqTable a where Source #
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".
Minimal complete definition
Nothing
Methods
Instances
(==:) :: forall a. EqTable a => a -> a -> Expr Bool infix 4 Source #
Compare two Tables for equality. This corresponds to comparing all
columns inside each table for equality, and combining all comparisons with
AND.
(/=:) :: forall a. EqTable a => a -> a -> Expr Bool infix 4 Source #
Test if two Tables are different. This corresponds to comparing all
columns inside each table for inequality, and combining all comparisons with
OR.
class EqTable a => OrdTable a where Source #
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".
Minimal complete definition
Nothing
Methods
Instances
(<:) :: forall a. OrdTable a => a -> a -> Expr Bool infix 4 Source #
Test if one Table sorts before another. Corresponds to comparing all
columns with <.
(<=:) :: forall a. OrdTable a => a -> a -> Expr Bool infix 4 Source #
Test if one Table sorts before, or is equal to, another. Corresponds to
comparing all columns with <=.
(>:) :: forall a. OrdTable a => a -> a -> Expr Bool infix 4 Source #
Test if one Table sorts after another. Corresponds to comparing all
columns with >.
(>=:) :: forall a. OrdTable a => a -> a -> Expr Bool infix 4 Source #
Test if one Table sorts after another. Corresponds to comparing all
columns with >=.
ascTable :: forall a. OrdTable a => Order a Source #
Construct an Order for a Table by sorting all columns into ascending
orders (any nullable columns will be sorted with NULLS FIRST).
descTable :: forall a. OrdTable a => Order a Source #
Construct an Order for a Table by sorting all columns into descending
orders (any nullable columns will be sorted with NULLS LAST).
greatest :: OrdTable a => a -> a -> a Source #
Given two Tables, return the table that sorts after the other.
least :: OrdTable a => a -> a -> a Source #
Given two Tables, return the table that sorts before the other.
lit :: forall exprs a. Serializable exprs a => a -> exprs Source #
Use lit to turn literal Haskell values into expressions. lit is
capable of lifting single Exprs to full tables.
bool :: Table Expr a => a -> a -> Expr Bool -> a Source #
An if-then-else expression on tables.
bool x y p returns x if p is False, and returns y if p is
True.
case_ :: Table Expr a => [(Expr Bool, a)] -> a -> a Source #
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.
castTable :: Table Expr a => a -> a Source #
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.
MaybeTable
data MaybeTable context a Source #
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.
Instances
| (Table context a, Reifiable context, context ~ context') => Table context' (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe Associated Types type Columns (MaybeTable context a) :: HTable Source # type Context (MaybeTable context a) :: Context Source # type FromExprs (MaybeTable context a) Source # type Transpose context' (MaybeTable context a) Source # Methods toColumns :: MaybeTable context a -> Columns (MaybeTable context a) context' Source # fromColumns :: Columns (MaybeTable context a) context' -> MaybeTable context a Source # fromResult :: Columns (MaybeTable context a) Result -> FromExprs (MaybeTable context a) Source # toResult :: FromExprs (MaybeTable context a) -> Columns (MaybeTable context a) Result Source # | |
| context ~ Expr => Applicative (MaybeTable context) Source # | Has the same behavior as the |
Defined in Rel8.Table.Maybe Methods pure :: a -> MaybeTable context a # (<*>) :: MaybeTable context (a -> b) -> MaybeTable context a -> MaybeTable context b # liftA2 :: (a -> b -> c) -> MaybeTable context a -> MaybeTable context b -> MaybeTable context c # (*>) :: MaybeTable context a -> MaybeTable context b -> MaybeTable context b # (<*) :: MaybeTable context a -> MaybeTable context b -> MaybeTable context a # | |
| Nullifiable context => Functor (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods fmap :: (a -> b) -> MaybeTable context a -> MaybeTable context b # (<$) :: a -> MaybeTable context b -> MaybeTable context a # | |
| context ~ Expr => Monad (MaybeTable context) Source # | Has the same behavior as the |
Defined in Rel8.Table.Maybe Methods (>>=) :: MaybeTable context a -> (a -> MaybeTable context b) -> MaybeTable context b # (>>) :: MaybeTable context a -> MaybeTable context b -> MaybeTable context b # return :: a -> MaybeTable context a # | |
| context ~ Expr => AltTable (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods (<|>:) :: Table Expr a => MaybeTable context a -> MaybeTable context a -> MaybeTable context a Source # | |
| context ~ Expr => AlternativeTable (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods emptyTable :: Table Expr a => MaybeTable context a Source # | |
| Projectable (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods project :: Projecting a b => Projection a b -> MaybeTable context a -> MaybeTable context b Source # | |
| context ~ Expr => Apply (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods (<.>) :: MaybeTable context (a -> b) -> MaybeTable context a -> MaybeTable context b # (.>) :: MaybeTable context a -> MaybeTable context b -> MaybeTable context b # (<.) :: MaybeTable context a -> MaybeTable context b -> MaybeTable context a # liftF2 :: (a -> b -> c) -> MaybeTable context a -> MaybeTable context b -> MaybeTable context c # | |
| context ~ Expr => Bind (MaybeTable context) Source # | |
Defined in Rel8.Table.Maybe Methods (>>-) :: MaybeTable context a -> (a -> MaybeTable context b) -> MaybeTable context b # join :: MaybeTable context (MaybeTable context a) -> MaybeTable context a # | |
| (context ~ Expr, Table Expr a, Semigroup a) => Monoid (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe Methods mempty :: MaybeTable context a # mappend :: MaybeTable context a -> MaybeTable context a -> MaybeTable context a # mconcat :: [MaybeTable context a] -> MaybeTable context a # | |
| (context ~ Expr, Table Expr a, Semigroup a) => Semigroup (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe Methods (<>) :: MaybeTable context a -> MaybeTable context a -> MaybeTable context a # sconcat :: NonEmpty (MaybeTable context a) -> MaybeTable context a # stimes :: Integral b => b -> MaybeTable context a -> MaybeTable context a # | |
| (EqTable a, context ~ Expr) => EqTable (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe | |
| (OrdTable a, context ~ Expr) => OrdTable (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe | |
| (ToExprs exprs a, context ~ Expr) => ToExprs (MaybeTable context exprs) (Maybe a) Source # | |
Defined in Rel8.Table.Maybe | |
| type Transpose to (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe | |
| type Columns (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe | |
| type Context (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe | |
| type FromExprs (MaybeTable context a) Source # | |
Defined in Rel8.Table.Maybe | |
maybeTable :: Table Expr b => b -> (a -> b) -> MaybeTable Expr a -> b Source #
Perform case analysis on a MaybeTable. Like maybe.
($?) :: forall a b. Sql DBType b => (a -> Expr b) -> MaybeTable Expr a -> Expr (Nullify b) infixl 4 Source #
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.
nothingTable :: Table Expr a => MaybeTable Expr a Source #
The null table. Like Nothing.
justTable :: a -> MaybeTable Expr a Source #
Lift any table into MaybeTable. Like Just. Note you can also use
pure.
isNothingTable :: MaybeTable Expr a -> Expr Bool Source #
Check if a MaybeTable is absent of any row. Like isNothing.
isJustTable :: MaybeTable Expr a -> Expr Bool Source #
Check if a MaybeTable contains a row. Like isJust.
fromMaybeTable :: Table Expr a => a -> MaybeTable Expr a -> a Source #
fromMaybe for MaybeTables.
optional :: Query a -> Query (MaybeTable Expr a) Source #
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.
catMaybeTable :: MaybeTable Expr a -> Query a Source #
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.
traverseMaybeTable :: (a -> Query b) -> MaybeTable Expr a -> Query (MaybeTable Expr b) Source #
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.
aggregateMaybeTable :: Aggregator' fold i a -> Aggregator1 (MaybeTable Expr i) (MaybeTable Expr a) Source #
Lift an aggregator to operate on a MaybeTable. nothingTables and
justTables are grouped separately.
Arguments
| :: Name (Maybe MaybeTag) | The name of the column to track whether a row is a |
| -> a | Names of the columns in |
| -> MaybeTable Name 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.
EitherTable
data EitherTable context a b Source #
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.
Instances
| (Table context a, Table context b, Reifiable context, context ~ context') => Table context' (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either Associated Types type Columns (EitherTable context a b) :: HTable Source # type Context (EitherTable context a b) :: Context Source # type FromExprs (EitherTable context a b) Source # type Transpose context' (EitherTable context a b) Source # Methods toColumns :: EitherTable context a b -> Columns (EitherTable context a b) context' Source # fromColumns :: Columns (EitherTable context a b) context' -> EitherTable context a b Source # fromResult :: Columns (EitherTable context a b) Result -> FromExprs (EitherTable context a b) Source # toResult :: FromExprs (EitherTable context a b) -> Columns (EitherTable context a b) Result Source # | |
| Nullifiable context => Bifunctor (EitherTable context) Source # | |
Defined in Rel8.Table.Either Methods bimap :: (a -> b) -> (c -> d) -> EitherTable context a c -> EitherTable context b d # first :: (a -> b) -> EitherTable context a c -> EitherTable context b c # second :: (b -> c) -> EitherTable context a b -> EitherTable context a c # | |
| Biprojectable (EitherTable context) Source # | |
Defined in Rel8.Table.Either Methods biproject :: (Projecting a b, Projecting c d) => Projection a b -> Projection c d -> EitherTable context a c -> EitherTable context b d Source # | |
| (context ~ Expr, Table Expr a) => Applicative (EitherTable context a) Source # | |
Defined in Rel8.Table.Either Methods pure :: a0 -> EitherTable context a a0 # (<*>) :: EitherTable context a (a0 -> b) -> EitherTable context a a0 -> EitherTable context a b # liftA2 :: (a0 -> b -> c) -> EitherTable context a a0 -> EitherTable context a b -> EitherTable context a c # (*>) :: EitherTable context a a0 -> EitherTable context a b -> EitherTable context a b # (<*) :: EitherTable context a a0 -> EitherTable context a b -> EitherTable context a a0 # | |
| Nullifiable context => Functor (EitherTable context a) Source # | |
Defined in Rel8.Table.Either Methods fmap :: (a0 -> b) -> EitherTable context a a0 -> EitherTable context a b # (<$) :: a0 -> EitherTable context a b -> EitherTable context a a0 # | |
| (context ~ Expr, Table Expr a) => Monad (EitherTable context a) Source # | |
Defined in Rel8.Table.Either Methods (>>=) :: EitherTable context a a0 -> (a0 -> EitherTable context a b) -> EitherTable context a b # (>>) :: EitherTable context a a0 -> EitherTable context a b -> EitherTable context a b # return :: a0 -> EitherTable context a a0 # | |
| Projectable (EitherTable context a) Source # | |
Defined in Rel8.Table.Either Methods project :: Projecting a0 b => Projection a0 b -> EitherTable context a a0 -> EitherTable context a b Source # | |
| (context ~ Expr, Table Expr a) => Apply (EitherTable context a) Source # | |
Defined in Rel8.Table.Either Methods (<.>) :: EitherTable context a (a0 -> b) -> EitherTable context a a0 -> EitherTable context a b # (.>) :: EitherTable context a a0 -> EitherTable context a b -> EitherTable context a b # (<.) :: EitherTable context a a0 -> EitherTable context a b -> EitherTable context a a0 # liftF2 :: (a0 -> b -> c) -> EitherTable context a a0 -> EitherTable context a b -> EitherTable context a c # | |
| (context ~ Expr, Table Expr a) => Bind (EitherTable context a) Source # | |
Defined in Rel8.Table.Either Methods (>>-) :: EitherTable context a a0 -> (a0 -> EitherTable context a b) -> EitherTable context a b # join :: EitherTable context a (EitherTable context a a0) -> EitherTable context a a0 # | |
| (context ~ Expr, Table Expr a, Table Expr b) => Semigroup (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either Methods (<>) :: EitherTable context a b -> EitherTable context a b -> EitherTable context a b # sconcat :: NonEmpty (EitherTable context a b) -> EitherTable context a b # stimes :: Integral b0 => b0 -> EitherTable context a b -> EitherTable context a b # | |
| (EqTable a, EqTable b, context ~ Expr) => EqTable (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either | |
| (OrdTable a, OrdTable b, context ~ Expr) => OrdTable (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either | |
| type Transpose to (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either | |
| type Columns (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either | |
| type Context (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either | |
| type FromExprs (EitherTable context a b) Source # | |
Defined in Rel8.Table.Either | |
eitherTable :: Table Expr c => (a -> c) -> (b -> c) -> EitherTable Expr a b -> c Source #
Pattern match/eliminate an EitherTable, by providing mappings from a
leftTable and rightTable.
leftTable :: Table Expr b => a -> EitherTable Expr a b Source #
Construct a left EitherTable. Like Left.
rightTable :: Table Expr a => b -> EitherTable Expr a b Source #
Construct a right EitherTable. Like Right.
isLeftTable :: EitherTable Expr a b -> Expr Bool Source #
Test if an EitherTable is a leftTable.
isRightTable :: EitherTable Expr a b -> Expr Bool Source #
Test if an EitherTable is a rightTable.
keepLeftTable :: EitherTable Expr a b -> Query a Source #
Filter EitherTables, keeping only leftTables.
keepRightTable :: EitherTable Expr a b -> Query b Source #
Filter EitherTables, keeping only rightTables.
bitraverseEitherTable :: (a -> Query c) -> (b -> Query d) -> EitherTable Expr a b -> Query (EitherTable Expr c d) Source #
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 ]
aggregateEitherTable :: Aggregator' fold i a -> Aggregator' fold' i' b -> Aggregator1 (EitherTable Expr i i') (EitherTable Expr a b) Source #
Lift a pair aggregators to operate on an EitherTable. leftTables and
rightTables are grouped separately.
Arguments
| :: Name EitherTag | The name of the column to track whether a row is a |
| -> a | Names of the columns in the |
| -> b | Names of the columns in the |
| -> EitherTable Name 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.
TheseTable
data TheseTable context a b Source #
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.
Instances
| (Table context a, Table context b, Reifiable context, context ~ context') => Table context' (TheseTable context a b) Source # | |
Defined in Rel8.Table.These Associated Types type Columns (TheseTable context a b) :: HTable Source # type Context (TheseTable context a b) :: Context Source # type FromExprs (TheseTable context a b) Source # type Transpose context' (TheseTable context a b) Source # Methods toColumns :: TheseTable context a b -> Columns (TheseTable context a b) context' Source # fromColumns :: Columns (TheseTable context a b) context' -> TheseTable context a b Source # fromResult :: Columns (TheseTable context a b) Result -> FromExprs (TheseTable context a b) Source # toResult :: FromExprs (TheseTable context a b) -> Columns (TheseTable context a b) Result Source # | |
| Nullifiable context => Bifunctor (TheseTable context) Source # | |
Defined in Rel8.Table.These Methods bimap :: (a -> b) -> (c -> d) -> TheseTable context a c -> TheseTable context b d # first :: (a -> b) -> TheseTable context a c -> TheseTable context b c # second :: (b -> c) -> TheseTable context a b -> TheseTable context a c # | |
| Biprojectable (TheseTable context) Source # | |
Defined in Rel8.Table.These Methods biproject :: (Projecting a b, Projecting c d) => Projection a b -> Projection c d -> TheseTable context a c -> TheseTable context b d Source # | |
| (context ~ Expr, Table Expr a, Semigroup a) => Applicative (TheseTable context a) Source # | |
Defined in Rel8.Table.These Methods pure :: a0 -> TheseTable context a a0 # (<*>) :: TheseTable context a (a0 -> b) -> TheseTable context a a0 -> TheseTable context a b # liftA2 :: (a0 -> b -> c) -> TheseTable context a a0 -> TheseTable context a b -> TheseTable context a c # (*>) :: TheseTable context a a0 -> TheseTable context a b -> TheseTable context a b # (<*) :: TheseTable context a a0 -> TheseTable context a b -> TheseTable context a a0 # | |
| Nullifiable context => Functor (TheseTable context a) Source # | |
Defined in Rel8.Table.These Methods fmap :: (a0 -> b) -> TheseTable context a a0 -> TheseTable context a b # (<$) :: a0 -> TheseTable context a b -> TheseTable context a a0 # | |
| (context ~ Expr, Table Expr a, Semigroup a) => Monad (TheseTable context a) Source # | |
Defined in Rel8.Table.These Methods (>>=) :: TheseTable context a a0 -> (a0 -> TheseTable context a b) -> TheseTable context a b # (>>) :: TheseTable context a a0 -> TheseTable context a b -> TheseTable context a b # return :: a0 -> TheseTable context a a0 # | |
| Projectable (TheseTable context a) Source # | |
Defined in Rel8.Table.These Methods project :: Projecting a0 b => Projection a0 b -> TheseTable context a a0 -> TheseTable context a b Source # | |
| (context ~ Expr, Table Expr a, Semigroup a) => Apply (TheseTable context a) Source # | |
Defined in Rel8.Table.These Methods (<.>) :: TheseTable context a (a0 -> b) -> TheseTable context a a0 -> TheseTable context a b # (.>) :: TheseTable context a a0 -> TheseTable context a b -> TheseTable context a b # (<.) :: TheseTable context a a0 -> TheseTable context a b -> TheseTable context a a0 # liftF2 :: (a0 -> b -> c) -> TheseTable context a a0 -> TheseTable context a b -> TheseTable context a c # | |
| (context ~ Expr, Table Expr a, Semigroup a) => Bind (TheseTable context a) Source # | |
Defined in Rel8.Table.These Methods (>>-) :: TheseTable context a a0 -> (a0 -> TheseTable context a b) -> TheseTable context a b # join :: TheseTable context a (TheseTable context a a0) -> TheseTable context a a0 # | |
| (context ~ Expr, Table Expr a, Table Expr b, Semigroup a, Semigroup b) => Semigroup (TheseTable context a b) Source # | |
Defined in Rel8.Table.These Methods (<>) :: TheseTable context a b -> TheseTable context a b -> TheseTable context a b # sconcat :: NonEmpty (TheseTable context a b) -> TheseTable context a b # stimes :: Integral b0 => b0 -> TheseTable context a b -> TheseTable context a b # | |
| (EqTable a, EqTable b, context ~ Expr) => EqTable (TheseTable context a b) Source # | |
Defined in Rel8.Table.These | |
| (OrdTable a, OrdTable b, context ~ Expr) => OrdTable (TheseTable context a b) Source # | |
Defined in Rel8.Table.These | |
| type Transpose to (TheseTable context a b) Source # | |
Defined in Rel8.Table.These | |
| type Columns (TheseTable context a b) Source # | |
Defined in Rel8.Table.These | |
| type Context (TheseTable context a b) Source # | |
Defined in Rel8.Table.These | |
| type FromExprs (TheseTable context a b) Source # | |
Defined in Rel8.Table.These | |
theseTable :: Table Expr c => (a -> c) -> (b -> c) -> (a -> b -> c) -> TheseTable Expr a b -> c Source #
Pattern match on a TheseTable. Corresponds to these.
thisTable :: Table Expr b => a -> TheseTable Expr a b Source #
Construct a TheseTable. Corresponds to This.
thatTable :: Table Expr a => b -> TheseTable Expr a b Source #
Construct a TheseTable. Corresponds to That.
thoseTable :: a -> b -> TheseTable Expr a b Source #
Construct a TheseTable. Corresponds to These.
isThisTable :: TheseTable Expr a b -> Expr Bool Source #
Test if a TheseTable was constructed with thisTable.
Corresponds to isThis.
isThatTable :: TheseTable Expr a b -> Expr Bool Source #
Test if a TheseTable was constructed with thatTable.
Corresponds to isThat.
isThoseTable :: TheseTable Expr a b -> Expr Bool Source #
Test if a TheseTable was constructed with thoseTable.
Corresponds to isThese.
hasHereTable :: TheseTable Expr a b -> Expr Bool Source #
Test if the a side of TheseTable a b is present.
Corresponds to hasHere.
hasThereTable :: TheseTable Expr a b -> Expr Bool Source #
Test if the b table of TheseTable a b is present.
Corresponds to hasThere.
justHereTable :: TheseTable context a b -> MaybeTable context a Source #
Attempt to project out the a table of a TheseTable a b.
Corresponds to justHere.
justThereTable :: TheseTable context a b -> MaybeTable context b Source #
Attempt to project out the b table of a TheseTable a b.
Corresponds to justThere.
alignMaybeTable :: MaybeTable Expr a -> MaybeTable Expr b -> MaybeTable Expr (TheseTable Expr a b) Source #
Construct a TheseTable from two MaybeTables.
alignBy :: (a -> b -> Expr Bool) -> Query a -> Query b -> Query (TheseTable Expr a b) Source #
Corresponds to a FULL OUTER JOIN between two queries.
keepHereTable :: TheseTable Expr a b -> Query (a, MaybeTable Expr b) Source #
loseHereTable :: TheseTable Expr a b -> Query b Source #
keepThereTable :: TheseTable Expr a b -> Query (MaybeTable Expr a, b) Source #
loseThereTable :: TheseTable Expr a b -> Query a Source #
keepThisTable :: TheseTable Expr a b -> Query a Source #
loseThisTable :: TheseTable Expr a b -> Query (MaybeTable Expr a, b) Source #
keepThatTable :: TheseTable Expr a b -> Query b Source #
loseThatTable :: TheseTable Expr a b -> Query (a, MaybeTable Expr b) Source #
keepThoseTable :: TheseTable Expr a b -> Query (a, b) Source #
loseThoseTable :: TheseTable Expr a b -> Query (EitherTable Expr a b) Source #
bitraverseTheseTable :: (a -> Query c) -> (b -> Query d) -> TheseTable Expr a b -> Query (TheseTable Expr c d) Source #
aggregateTheseTable :: Aggregator' fold i a -> Aggregator' fold' i' b -> Aggregator1 (TheseTable Expr i i') (TheseTable Expr a b) Source #
Lift a pair aggregators to operate on a TheseTable. thisTables,
thatTables are thoseTables are grouped separately.
Arguments
| :: Name (Maybe MaybeTag) | The name of the column to track the presence of the |
| -> Name (Maybe MaybeTag) | The name of the column to track the presence of the |
| -> a | Names of the columns in the |
| -> b | Names of the columns in the |
| -> TheseTable Name 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.
ListTable
data ListTable context a Source #
A ListTable value contains zero or more instances of a. You construct
ListTables with many or listAgg.
Instances
listTable :: Table Expr a => [a] -> ListTable Expr a Source #
Construct a ListTable from a list of expressions.
($*) :: Projecting a (Expr b) => Projection a (Expr b) -> ListTable Expr a -> Expr [b] infixl 4 Source #
Project a single expression out of a ListTable.
many :: Table Expr a => Query a -> Query (ListTable Expr a) Source #
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.
manyExpr :: Sql DBType a => Query (Expr a) -> Query (Expr [a]) Source #
A version of many specialised to single expressions.
NonEmptyTable
data NonEmptyTable context a Source #
A NonEmptyTable value contains one or more instances of a. You
construct NonEmptyTables with some or nonEmptyAgg.
Instances
nonEmptyTable :: Table Expr a => NonEmpty a -> NonEmptyTable Expr a Source #
Construct a NonEmptyTable from a non-empty list of expressions.
($+) :: Projecting a (Expr b) => Projection a (Expr b) -> NonEmptyTable Expr a -> Expr (NonEmpty b) infixl 4 Source #
Project a single expression out of a NonEmptyTable.
Arguments
| :: Table Name a | |
| => a | The names of the columns of elements of the list. |
| -> NonEmptyTable Name a |
Construct a NonEmptyTable in the Name context. This can be useful if
you have a NonEmptyTable that you are storing in a table and need to
construct a TableSchema.
some :: Table Expr a => Query a -> Query (NonEmptyTable Expr a) Source #
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.
someExpr :: Sql DBType a => Query (Expr a) -> Query (Expr (NonEmpty a)) Source #
A version of many specialised to single expressions.
catNonEmptyTable :: Table Expr a => NonEmptyTable Expr a -> Query a Source #
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.
NullTable
data NullTable context a Source #
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.
Instances
| (Table context a, Reifiable context, context ~ context') => Table context' (NullTable context a) Source # | |
Defined in Rel8.Table.Null Associated Types type Columns (NullTable context a) :: HTable Source # type Context (NullTable context a) :: Context Source # Methods toColumns :: NullTable context a -> Columns (NullTable context a) context' Source # fromColumns :: Columns (NullTable context a) context' -> NullTable context a Source # fromResult :: Columns (NullTable context a) Result -> FromExprs (NullTable context a) Source # toResult :: FromExprs (NullTable context a) -> Columns (NullTable context a) Result Source # | |
| context ~ Expr => AltTable (NullTable context) Source # | |
| context ~ Expr => AlternativeTable (NullTable context) Source # | |
Defined in Rel8.Table.Null | |
| Projectable (NullTable context) Source # | |
Defined in Rel8.Table.Null Methods project :: Projecting a b => Projection a b -> NullTable context a -> NullTable context b Source # | |
| (EqTable a, context ~ Expr) => EqTable (NullTable context a) Source # | |
| (OrdTable a, context ~ Expr) => OrdTable (NullTable context a) Source # | |
| (ToExprs exprs a, context ~ Expr) => ToExprs (NullTable context exprs) (Maybe a) Source # | |
Defined in Rel8.Table.Null | |
| type Transpose to (NullTable context a) Source # | |
Defined in Rel8.Table.Null | |
| type Columns (NullTable context a) Source # | |
Defined in Rel8.Table.Null | |
| type Context (NullTable context a) Source # | |
Defined in Rel8.Table.Null | |
| type FromExprs (NullTable context a) Source # | |
Defined in Rel8.Table.Null | |
nullableTable :: (Table Expr a, Table Expr b) => b -> (a -> b) -> NullTable Expr a -> b Source #
Like nullable.
isNonNullTable :: Table Expr a => NullTable Expr a -> Expr Bool Source #
The inverse of isNullTable.
nameNullTable :: a -> NullTable Name a Source #
toNullTable :: Table Expr a => MaybeTable Expr a -> NullTable Expr a Source #
Convert a MaybeTable to a NullTable. Note that if the underlying a
has no non-nullable fields, this is a lossy conversion.
toMaybeTable :: Table Expr a => NullTable Expr a -> MaybeTable Expr a Source #
Convert a NullTable to a MaybeTable.
Algebraic data types / sum types
Algebraic data types can be modelled between Haskell and SQL.
- Your SQL table needs a certain text field that tags which Haskell constructor is in use.
- You have to use a few combinators to specify the sum type's individual constructors.
- If you want to do case analysis at the
Expr(SQL) level, you can usemaybe/either-like eliminators.
The documentation in this section will assume a set of database types like this:
data Thing f = ThingEmployer (Employer f) | ThingPotato (Potato f) | Nullary
deriving stock Generic
data Employer f = Employer { employerId :: f Int32, employerName :: f Text}
deriving stock Generic
deriving anyclass Rel8able
data Potato f = Potato { size :: f Int32, grower :: f Text }
deriving stock Generic
deriving anyclass Rel8able
Naming of ADTs
First, in your TableSchema, name your type like this:
thingSchema :: TableSchema (ADT Thing Name)
thingSchema =
TableSchema
{ schema = Nothing,
name = "thing",
columns =
nameADT @Thing
"tag"
Employer
{ employerName = "name",
employerId = "id"
}
Potato {size = "size", grower = "Mary"}
}
Note that nameADT @Thing "tag" is variadic: it accepts one
argument per constructor, except the nullary ones (Nullary) because
there's nothing to do for them.
Instances
| ADTable t => Rel8able (ADT t) Source # | |
Defined in Rel8.Table.ADT Methods gfromColumns :: forall (context :: Context). SContext context -> GColumns (ADT t) context -> ADT t context gtoColumns :: forall (context :: Context). SContext context -> ADT t context -> GColumns (ADT t) context gfromResult :: GColumns (ADT t) Result -> GFromExprs (ADT t) | |
class (Generic (Record (t Result)), HTable (GColumnsADT t), GSerializeADT TSerialize TColumns (Eval (ADTRep t Expr)) (Eval (ADTRep t Result))) => ADTable t Source #
Deconstruction of ADTs
To deconstruct sum types at the SQL level, use deconstructADT,
which is also variadic, and has one argument for each
constructor. Similar to maybe.
query :: Query (ADT Thing Expr)
query = do
thingExpr <- each thingSchema
where_ $
deconstructADT @Thing
(\employer -> employerName employer ==. lit "Mary")
(\potato -> grower potato ==. lit "Mary")
(lit False) -- Nullary case
thingExpr
pure thingExpr
SQL output:
SELECT
CAST("tag0_1" AS text) as "tag",
CAST("id1_1" AS int4) as "ThingEmployer_1employerId",
CAST("name2_1" AS text) as "ThingEmployer_1employerName",
CAST("size3_1" AS int4) as "ThingPotato_1size",
CAST(Mary4_1 AS text) as "ThingPotato_1grower"
FROM (SELECT
*
FROM (SELECT
"tag" as "tag0_1",
"id" as "id1_1",
"name" as "name2_1",
"size" as "size3_1",
Mary as Mary4_1
FROM "thing" as T1) as T1
WHERE (CASE WHEN ("tag0_1") = (CAST(EThingPotato AS text)) THEN (Mary4_1) = (CAST(EMary AS text))
WHEN ("tag0_1") = (CAST(ENullary AS text)) THEN CAST(FALSE AS bool) ELSE ("name2_1") = (CAST(EMary AS text)) END)) as T1
type DeconstructADT t r = GGDeconstruct 'Sum (ADTRep t) (ADT t Expr) r Source #
deconstructADT :: forall t r. (ConstructableADT t, Table Expr r) => DeconstructADT t r Source #
Construction of ADTs
To construct an ADT, you can use buildADT or constructADT. Consider the following type:
data Task f = Pending | Complete (CompletedTask f)
buildADT is for constructing values of Task in the Expr
context. buildADT needs two type-level arguments before its type
makes any sense. The first argument is the type of the ADT, which
in our case is Task. The second is the name of the constructor we
want to use. So that means we have the following possible
instantiations of buildADT for Task:
> :t buildADT @Task @"Pending" buildADT @Task @"Pending" :: ADT Task Expr > :t buildADT @Task @"Complete" buildADT @Task @"Complete" :: CompletedTask Expr -> ADT Task Expr
Note that as the Pending constructor has no fields, buildADT
@Task @Pending is equivalent to lit Pending. But buildADT
@Task @Complete is not the same as lit . Complete:
> :t lit . Complete lit . Complete :: CompletedTask Result -> ADT Task Expr
Note that the former takes a CompletedTask Expr while the latter
takes a CompletedTask Result. The former is more powerful because
you can construct Tasks using dynamic values coming a database
query.
To show what this can look like in SQL, consider:
> :{
showQuery $ values
[ buildADT @Task @"Pending"
, buildADT @Task @"Complete" CompletedTask {date = Rel8.Expr.Time.now}
]
:}
This produces the following SQL:
SELECT
CAST("values0_1" AS text) as "tag",
CAST("values1_1" AS timestamptz) as "Complete_1date"
FROM (SELECT
*
FROM (SELECT "column1" as "values0_1",
"column2" as "values1_1"
FROM
(VALUES
(CAST(EPending AS text),CAST(NULL AS timestamptz)),
(CAST(EComplete AS text),CAST(now() AS timestamptz))) as "V") as "T1") as "T1"
This is what you get if you run it in psql:
tag | Complete_1date ----------+------------------------------- Pending | Complete | 2022-05-19 21:28:23.969065+00 (2 rows)
"constructADT" is less convenient but more general alternative to "buildADT". It requires only one type-level argument for its type to make sense:
> :t constructADT Task
constructADT Task
:: (forall r. r -> (CompletedTask Expr -> r) -> r) -> ADT Task Expr
This might still seem a bit opaque, but basically it gives you a Church-encoded constructor for arbitrary algebraic data types. You might use it as follows:
let
pending :: ADT Task Expr
pending = constructADT @Task $ \pending _complete -> pending
complete :: ADT Task Expr
complete = constructADT @Task $ \_pending complete -> complete CompletedTask {date = Rel8.Expr.Time.now}
These values are otherwise identical to the ones we saw above with
buildADT, it's just a different style of constructing them.
type ConstructADT t = forall r. GGConstruct 'Sum (ADTRep t) r Source #
constructADT :: forall t. ConstructableADT t => ConstructADT t -> ADT t Expr Source #
Miscellaneous notes
- Note that the order of the arguments for all of these functions
is determined by the order of the constructors in the data
definition. If it were
data Task = Complete (CompletedTask f) | Pendingthen the order of all the invocations ofconstructADTanddeconstructADTwould need to change. - Maybe this is obvious, but just to spell it out: once you're in
the
Resultcontext, you can of course constructTaskvalues normally and use standard Haskell pattern-matching.constructADTanddeconstructADTare specifically only needed in theExprcontext, and they allow you to do the equivalent of pattern matching in PostgreSQL.
HKD
Instances
| HKDable a => Rel8able (HKD a) Source # | |
Defined in Rel8.Table.HKD Methods gfromColumns :: forall (context :: Context). SContext context -> GColumns (HKD a) context -> HKD a context gtoColumns :: forall (context :: Context). SContext context -> HKD a context -> GColumns (HKD a) context gfromResult :: GColumns (HKD a) Result -> GFromExprs (HKD a) | |
| (GTable (TTable f) TColumns (GRecord (GMap (TColumn f) (Rep a))), GColumns TColumns (GRecord (GMap (TColumn f) (Rep a))) ~ GColumnsHKD a, GContext TContext (GRecord (GMap (TColumn f) (Rep a))) ~ f, GRecordable (GMap (TColumn f) (Rep a))) => Generic (HKD a f) Source # | |
| type Rep (HKD a f) Source # | |
Defined in Rel8.Table.HKD | |
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 Source #
Instances
type ConstructHKD a = forall r. GGConstruct (GAlgebra (Rep a)) (HKDRep a) r Source #
constructHKD :: forall a. ConstructableHKD a => ConstructHKD a -> HKD a Expr Source #
deconstructHKD :: forall a r. (ConstructableHKD a, Table Expr r) => DeconstructHKD a r Source #
Table schemas
data TableSchema names Source #
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.
Constructors
| TableSchema | |
Fields
| |
Instances
| Functor TableSchema Source # | |
Defined in Rel8.Schema.Table Methods fmap :: (a -> b) -> TableSchema a -> TableSchema b # (<$) :: a -> TableSchema b -> TableSchema a # | |
data QualifiedName Source #
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.
Constructors
| QualifiedName | |
Instances
| IsString QualifiedName Source # | Constructs |
Defined in Rel8.Schema.QualifiedName Methods fromString :: String -> QualifiedName # | |
| Show QualifiedName Source # | |
Defined in Rel8.Schema.QualifiedName Methods showsPrec :: Int -> QualifiedName -> ShowS # show :: QualifiedName -> String # showList :: [QualifiedName] -> ShowS # | |
| Eq QualifiedName Source # | |
Defined in Rel8.Schema.QualifiedName Methods (==) :: QualifiedName -> QualifiedName -> Bool # (/=) :: QualifiedName -> QualifiedName -> Bool # | |
| Ord QualifiedName Source # | |
Defined in Rel8.Schema.QualifiedName Methods compare :: QualifiedName -> QualifiedName -> Ordering # (<) :: QualifiedName -> QualifiedName -> Bool # (<=) :: QualifiedName -> QualifiedName -> Bool # (>) :: QualifiedName -> QualifiedName -> Bool # (>=) :: QualifiedName -> QualifiedName -> Bool # max :: QualifiedName -> QualifiedName -> QualifiedName # min :: QualifiedName -> QualifiedName -> QualifiedName # | |
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.
Instances
| Sql DBType a => Table Name (Name a) Source # | |
| IsString (Name a) Source # | |
Defined in Rel8.Schema.Name Methods fromString :: String -> Name a # | |
| Show (Name a) Source # | |
| type Transpose to (Name a) Source # | |
Defined in Rel8.Schema.Name | |
| type Columns (Name a) Source # | |
Defined in Rel8.Schema.Name | |
| type Context (Name a) Source # | |
Defined in Rel8.Schema.Name | |
| type FromExprs (Name a) Source # | |
Defined in Rel8.Schema.Name | |
namesFromLabels :: Table Name a => a Source #
Construct a table in the Name context containing the names of all
columns. Nested column names will be combined with /.
See also: namesFromLabelsWith.
namesFromLabelsWith :: Table Name a => (NonEmpty String -> String) -> a Source #
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.
Expressions
Typed SQL expressions.
Instances
class (constraint (Unnullify a), Nullable a) => Sql constraint a Source #
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.
Instances
| (constraint (Unnullify a), Nullable a) => Sql constraint a Source # | |
Defined in Rel8.Schema.Null | |
litExpr :: Sql DBType a => a -> Expr a Source #
Produce an expression from a literal.
Note that you can usually use lit, but litExpr can solve problems
of inference in polymorphic code.
unsafeCastExpr :: forall b a. Sql DBType b => Expr a -> Expr b Source #
Cast an expression to a different type. Corresponds to a CAST() function
call.
unsafeLiteral :: String -> Expr a Source #
Unsafely construct an expression from literal SQL.
This is an escape hatch, and can be used if Rel8 can not adequately express the query you need. If you find yourself using this function, please let us know, as it may indicate that something is missing from Rel8!
null
class (Nullable a, IsMaybe a ~ 'False) => NotNull a Source #
nullify a means a cannot take null as a value.
class Nullable' (IsMaybe a) a => Nullable a Source #
Nullable a means that rel8 is able to check if the type a is a
type that can take null values or not.
Instances
| Nullable' (IsMaybe a) a => Nullable a Source # | |
Defined in Rel8.Schema.Null | |
class IsMaybe a ~ IsMaybe b => Homonullable a b Source #
Homonullable a b means that both a and b can be null, or neither
a or b can be null.
Instances
| IsMaybe a ~ IsMaybe b => Homonullable a b Source # | |
Defined in Rel8.Schema.Null | |
nullify :: NotNull a => Expr a -> Expr (Maybe a) Source #
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.
nullable :: Table Expr b => b -> (Expr a -> b) -> Expr (Maybe a) -> b Source #
Like maybe, but to eliminate null.
liftOpNull :: DBType c => (Expr a -> Expr b -> Expr c) -> Expr (Maybe a) -> Expr (Maybe b) -> Expr (Maybe c) Source #
coalesce :: Expr (Maybe Bool) -> Expr Bool Source #
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.
Boolean operations
class DBType a => DBEq a Source #
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.
Instances
(/=.) :: forall a. Sql DBEq a => Expr a -> Expr a -> Expr Bool infix 4 Source #
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 /=?.
(/=?) :: DBEq a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 Source #
Test if two expressions are different.
This corresponds to the SQL <> operator, though it will always return a
Bool.
boolExpr :: Expr a -> Expr a -> Expr Bool -> Expr a Source #
Eliminate a boolean-valued expression.
Corresponds to bool.
caseExpr :: [(Expr Bool, Expr a)] -> Expr a -> Expr a Source #
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.
like :: Expr Text -> Expr Text -> Expr Bool Source #
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
ilike :: Expr Text -> Expr Text -> Expr Bool Source #
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
Ordering
class DBEq a => DBOrd a Source #
The class of database types that support the <, <=, > and >=
operators.
Instances
(<.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 Source #
Corresponds to the SQL < operator. Note that this differs from SQL <
as null will sort below any other value. For a version of < that exactly
matches SQL, see (<?).
(<=.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 Source #
Corresponds to the SQL <= operator. Note that this differs from SQL <=
as null will sort below any other value. For a version of <= that exactly
matches SQL, see (<=?).
(>.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 Source #
Corresponds to the SQL > operator. Note that this differs from SQL >
as null will sort below any other value. For a version of > that exactly
matches SQL, see (>?).
(>=.) :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr Bool infix 4 Source #
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 (>=?).
(<?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 Source #
Corresponds to the SQL < operator. Returns null if either arguments
are null.
(<=?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 Source #
Corresponds to the SQL <= operator. Returns null if either arguments
are null.
(>?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 Source #
Corresponds to the SQL > operator. Returns null if either arguments
are null.
(>=?) :: DBOrd a => Expr (Maybe a) -> Expr (Maybe a) -> Expr Bool infix 4 Source #
Corresponds to the SQL >= operator. Returns null if either arguments
are null.
leastExpr :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr a Source #
Given two expressions, return the expression that sorts less than the other.
Corresponds to the SQL least() function.
greatestExpr :: forall a. Sql DBOrd a => Expr a -> Expr a -> Expr a Source #
Given two expressions, return the expression that sorts greater than the other.
Corresponds to the SQL greatest() function.
Functions
This type class is basically , where each column of the
Table ExprTable is an argument to the function, but it also has an additional
instance for () for calling functions with no arguments.
Minimal complete definition
arguments
binaryOperator :: Sql DBType c => QualifiedName -> Expr a -> Expr b -> Expr c Source #
Construct an expression by applying an infix binary operator to two operands.
queryFunction :: (Arguments input, Table Expr output) => QualifiedName -> input -> Query output Source #
Select each row from a function that returns a relation. This is
equivalent to FROM function(input).
Queries
The Query monad allows you to compose a SELECT query. This monad has
semantics similar to the list ([]) monad.
Instances
| Applicative Query Source # | |
| Functor Query Source # | |
| Monad Query Source # | |
| AltTable Query Source # | |
| AlternativeTable Query Source # |
|
Defined in Rel8.Query | |
| Projectable Query Source # | |
Defined in Rel8.Query Methods project :: Projecting a b => Projection a b -> Query a -> Query b Source # | |
| Apply Query Source # | |
| Bind Query Source # | |
| Table Expr a => Monoid (Query a) Source # | |
| Table Expr a => Semigroup (Query a) Source # | |
Projection
type Projection a b = Transpose (Field a) a -> Transpose (Field a) b Source #
A s is a special type of function Projection a ba -> b whereby the
resulting b is guaranteed to be composed only from columns contained in
a.
class Projectable f where Source #
means that Projectable ff is a kind of functor on Tables
that allows the mapping of a Projection over its underlying columns.
Instances
class Biprojectable p where Source #
means that Biprojectable pp is a kind of bifunctor on
Tables that allows the mapping of a pair of Projections over its
underlying columns.
Methods
biproject :: (Projecting a b, Projecting c d) => Projection a b -> Projection c d -> p a c -> p b d Source #
Map a pair of Projections over p.
Instances
| Biprojectable Tabulation Source # | |
Defined in Rel8.Tabulate Methods biproject :: (Projecting a b, Projecting c d) => Projection a b -> Projection c d -> Tabulation a c -> Tabulation b d Source # | |
| Biprojectable (EitherTable context) Source # | |
Defined in Rel8.Table.Either Methods biproject :: (Projecting a b, Projecting c d) => Projection a b -> Projection c d -> EitherTable context a c -> EitherTable context b d Source # | |
| Biprojectable (TheseTable context) Source # | |
Defined in Rel8.Table.These Methods biproject :: (Projecting a b, Projecting c d) => Projection a b -> Projection c d -> TheseTable context a c -> TheseTable context b d Source # | |
class (Transposes (Context a) (Field a) a (Transpose (Field a) a), Transposes (Context a) (Field a) b (Transpose (Field a) b)) => Projecting a b Source #
The constraint ensures that Projecting a b is a
usable Projection a bProjection.
Instances
| (Transposes (Context a) (Field a) a (Transpose (Field a) a), Transposes (Context a) (Field a) b (Transpose (Field a) b)) => Projecting a b Source # | |
Defined in Rel8.Table.Projection | |
A special context used in the construction of Projections.
Instances
| Sql DBType a => Table (Field table) (Field table a) Source # | |
Defined in Rel8.Schema.Field Associated Types type Columns (Field table a) :: HTable Source # type Context (Field table a) :: Context Source # Methods toColumns :: Field table a -> Columns (Field table a) (Field table) Source # fromColumns :: Columns (Field table a) (Field table) -> Field table a Source # fromResult :: Columns (Field table a) Result -> FromExprs (Field table a) Source # toResult :: FromExprs (Field table a) -> Columns (Field table a) Result Source # | |
| type Transpose to (Field table a) Source # | |
Defined in Rel8.Schema.Field | |
| type Columns (Field table a) Source # | |
Defined in Rel8.Schema.Field | |
| type Context (Field table a) Source # | |
Defined in Rel8.Schema.Field | |
| type FromExprs (Field table a) Source # | |
Defined in Rel8.Schema.Field | |
Selecting rows
class Transposes Name Expr names exprs => Selects names exprs Source #
Instances
| Transposes Name Expr names exprs => Selects names exprs Source # | |
Defined in Rel8.Schema.Name | |
each :: Selects names exprs => TableSchema names -> Query exprs Source #
Select each row from a table definition. This is equivalent to FROM
table.
Filtering
where_ :: Expr Bool -> Query () Source #
Drop any rows that don't match a predicate. where_ expr is equivalent
to the SQL WHERE expr.
present :: Query a -> Query () Source #
Produce the empty query if the given query returns no rows. present
is equivalent to WHERE EXISTS in SQL.
absent :: Query a -> Query () Source #
Produce the empty query if the given query returns rows. absent
is equivalent to WHERE NOT EXISTS in SQL.
distinct :: EqTable a => Query a -> Query a Source #
Select all distinct rows from a query, removing duplicates. distinct q
is equivalent to the SQL statement SELECT DISTINCT q.
distinctOn :: EqTable b => (a -> b) -> Query a -> Query a Source #
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.
distinctOnBy :: EqTable b => (a -> b) -> Order a -> Query a -> Query a Source #
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.
LIMIT/OFFSET
limit :: Word -> Query a -> Query a Source #
limit n select at most n rows from a query. limit n is equivalent
to the SQL LIMIT n.
offset :: Word -> Query a -> Query a Source #
offset n drops the first n rows from a query. offset n is equivalent
to the SQL OFFSET n.
UNION
union :: EqTable a => Query a -> Query a -> Query a Source #
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.
unionAll :: Table Expr a => Query a -> Query a -> Query a Source #
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.
INTERSECT
intersect :: EqTable a => Query a -> Query a -> Query a Source #
Find the intersection of two queries, collapsing duplicates. intersect a
b is the same as the SQL statement a INTERSECT b.
intersectAll :: EqTable a => Query a -> Query a -> Query a Source #
Find the intersection of two queries, retaining duplicates. intersectAll
a b is the same as the SQL statement a INTERSECT ALL b.
EXCEPT
except :: EqTable a => Query a -> Query a -> Query a Source #
Find the difference of two queries, collapsing duplicates except a b is
the same as the SQL statement a EXCEPT b.
exceptAll :: EqTable a => Query a -> Query a -> Query a Source #
Find the difference of two queries, retaining duplicates. exceptAll a b
is the same as the SQL statement a EXCEPT ALL b.
EXISTS
withBy :: (a -> b -> Expr Bool) -> Query b -> a -> Query a Source #
Like with, but with a custom membership test.
withoutBy :: (a -> b -> Expr Bool) -> Query b -> a -> Query a Source #
Like without, but with a custom membership test.
WITH
materialize :: (Table Expr a, Table Expr b) => Query a -> (Query a -> Query b) -> Query b Source #
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.
WITH RECURSIVE
loop :: Table Expr a => Query a -> (a -> Query a) -> Query a Source #
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, is the smallest set of rows loop s fr such
that
r == s `unionAll` (r >>= f)
Operationally, takes each row in an initial set loop s fs 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.
loopDistinct :: Table Expr a => Query a -> (a -> Query a) -> Query a Source #
loopDistinct is like loop but uses UNION instead of UNION ALL to
combine the recursive and non-recursive terms.
Denotationally, is the smallest set of rows
loopDistinct s fr such that
r == s `union` (r >>= f)
Operationally, takes each distinct row in an
initial set loopDistinct s fs 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.
Aggregation
type Aggregator = Aggregator' 'Full Source #
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 Aggregator1 = Aggregator' 'Semi Source #
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.
data Aggregator' fold i a Source #
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 Aggregator's 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 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
}
Instances
| ProductProfunctor (Aggregator' fold) Source # | |
Defined in Rel8.Aggregate Methods purePP :: b -> Aggregator' fold a b # (****) :: Aggregator' fold a (b -> c) -> Aggregator' fold a b -> Aggregator' fold a c # empty :: Aggregator' fold () () # (***!) :: Aggregator' fold a b -> Aggregator' fold a' b' -> Aggregator' fold (a, a') (b, b') # | |
| SumProfunctor (Aggregator' fold) Source # | |
Defined in Rel8.Aggregate Methods (+++!) :: Aggregator' fold a b -> Aggregator' fold a' b' -> Aggregator' fold (Either a a') (Either b b') # | |
| Profunctor (Aggregator' fold) Source # | |
Defined in Rel8.Aggregate Methods dimap :: (a -> b) -> (c -> d) -> Aggregator' fold b c -> Aggregator' fold a d # lmap :: (a -> b) -> Aggregator' fold b c -> Aggregator' fold a c # rmap :: (b -> c) -> Aggregator' fold a b -> Aggregator' fold a c # (#.) :: forall a b c q. Coercible c b => q b c -> Aggregator' fold a b -> Aggregator' fold a c # (.#) :: forall a b c q. Coercible b a => Aggregator' fold b c -> q a b -> Aggregator' fold a c # | |
| Applicative (Aggregator' fold i) Source # | |
Defined in Rel8.Aggregate Methods pure :: a -> Aggregator' fold i a # (<*>) :: Aggregator' fold i (a -> b) -> Aggregator' fold i a -> Aggregator' fold i b # liftA2 :: (a -> b -> c) -> Aggregator' fold i a -> Aggregator' fold i b -> Aggregator' fold i c # (*>) :: Aggregator' fold i a -> Aggregator' fold i b -> Aggregator' fold i b # (<*) :: Aggregator' fold i a -> Aggregator' fold i b -> Aggregator' fold i a # | |
| Functor (Aggregator' fold i) Source # | |
Defined in Rel8.Aggregate Methods fmap :: (a -> b) -> Aggregator' fold i a -> Aggregator' fold i b # (<$) :: a -> Aggregator' fold i b -> Aggregator' fold i a # | |
| Apply (Aggregator' fold i) Source # | |
Defined in Rel8.Aggregate Methods (<.>) :: Aggregator' fold i (a -> b) -> Aggregator' fold i a -> Aggregator' fold i b # (.>) :: Aggregator' fold i a -> Aggregator' fold i b -> Aggregator' fold i b # (<.) :: Aggregator' fold i a -> Aggregator' fold i b -> Aggregator' fold i a # liftF2 :: (a -> b -> c) -> Aggregator' fold i a -> Aggregator' fold i b -> Aggregator' fold i c # | |
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.
toAggregator :: a -> Aggregator' fold i a -> Aggregator' fold' i a Source #
Given a value to fall back on if given an empty collection of rows,
toAggregator turns an Aggregator1 into an Aggregator'.
toAggregator1 :: Aggregator' fold i a -> Aggregator1 i a Source #
toAggregator1 turns an Aggregator' into an Aggregator1.
aggregate :: (Table Expr i, Table Expr a) => Aggregator i a -> Query i -> Query a Source #
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.
aggregate1 :: Table Expr i => Aggregator' fold i a -> Query i -> Query a Source #
Apply an Aggregator1 to all rows returned by a Query. If
the Query is empty, then zero rows are returned.
filterWhere :: Table Expr a => (i -> Expr Bool) -> Aggregator i a -> Aggregator' fold i a Source #
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.
filterWhereOptional :: Table Expr a => (i -> Expr Bool) -> Aggregator' fold i a -> Aggregator' fold' i (MaybeTable Expr a) Source #
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.
distinctAggregate :: Aggregator' fold i a -> Aggregator' fold i a Source #
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.
orderAggregateBy :: Order i -> Aggregator' fold i a -> Aggregator' fold i a Source #
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.
optionalAggregate :: Table Expr a => Aggregator' fold i a -> Aggregator' fold' i (MaybeTable Expr a) Source #
optionalAggregate upgrades an Aggregator1 into an Aggregator' by
having it return nothingTable when aggregating over an empty collection
of rows.
countRows :: Query a -> Query (Expr Int64) Source #
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.
groupBy :: forall a. EqTable a => Aggregator1 a a Source #
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
groupByOn :: EqTable a => (i -> a) -> Aggregator1 i a Source #
Applies groupBy to the columns selected by the given function.
listAgg :: Table Expr a => Aggregator' fold a (ListTable Expr a) Source #
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)
listAggOn :: Table Expr a => (i -> a) -> Aggregator' fold i (ListTable Expr a) Source #
Applies listAgg to the columns selected by the given function.
listAggExpr :: Sql DBType a => Aggregator' fold (Expr a) (Expr [a]) Source #
Collect expressions values as a list.
listAggExprOn :: Sql DBType a => (i -> Expr a) -> Aggregator' fold i (Expr [a]) Source #
Applies listAggExpr to the column selected by the given function.
listCat :: Table Expr a => Aggregator' fold (ListTable Expr a) (ListTable Expr a) Source #
Concatenate lists into a single list.
listCatOn :: Table Expr a => (i -> ListTable Expr a) -> Aggregator' fold i (ListTable Expr a) Source #
Applies listCat to the list selected by the given function.
listCatExpr :: Sql DBType a => Aggregator' fold (Expr [a]) (Expr [a]) Source #
Concatenate lists into a single list.
listCatExprOn :: Sql DBType a => (i -> Expr [a]) -> Aggregator' fold i (Expr [a]) Source #
Applies listCatExpr to the column selected by the given function.
nonEmptyAgg :: Table Expr a => Aggregator1 a (NonEmptyTable Expr a) Source #
Like listAgg, but the result is guaranteed to be a non-empty list.
nonEmptyAggOn :: Table Expr a => (i -> a) -> Aggregator1 i (NonEmptyTable Expr a) Source #
Applies nonEmptyAgg to the columns selected by the given function.
nonEmptyAggExpr :: Sql DBType a => Aggregator1 (Expr a) (Expr (NonEmpty a)) Source #
Collect expressions values as a non-empty list.
nonEmptyAggExprOn :: Sql DBType a => (i -> Expr a) -> Aggregator1 i (Expr (NonEmpty a)) Source #
Applies nonEmptyAggExpr to the column selected by the given function.
nonEmptyCat :: Table Expr a => Aggregator1 (NonEmptyTable Expr a) (NonEmptyTable Expr a) Source #
Concatenate non-empty lists into a single non-empty list.
nonEmptyCatOn :: Table Expr a => (i -> NonEmptyTable Expr a) -> Aggregator1 i (NonEmptyTable Expr a) Source #
Applies nonEmptyCat to the non-empty list selected by the given
function.
nonEmptyCatExpr :: Sql DBType a => Aggregator1 (Expr (NonEmpty a)) (Expr (NonEmpty a)) Source #
Concatenate non-empty lists into a single non-empty list.
nonEmptyCatExprOn :: Sql DBType a => (i -> Expr (NonEmpty a)) -> Aggregator1 i (Expr (NonEmpty a)) Source #
Applies nonEmptyCatExpr to the column selected by the given function.
class DBOrd a => DBMax a Source #
The class of database types that support the max aggregation function.
Instances
max :: Sql DBMax a => Aggregator1 (Expr a) (Expr a) Source #
Produce an aggregation for Expr a using the max function.
maxOn :: Sql DBMax a => (i -> Expr a) -> Aggregator1 i (Expr a) Source #
Applies max to the column selected by the given function.
class DBOrd a => DBMin a Source #
The class of database types that support the min aggregation function.
Instances
min :: Sql DBMin a => Aggregator1 (Expr a) (Expr a) Source #
Produce an aggregation for Expr a using the min function.
minOn :: Sql DBMin a => (i -> Expr a) -> Aggregator1 i (Expr a) Source #
Applies min to the column selected by the given function.
class DBType a => DBSum a Source #
The class of database types that support the sum() aggregation function.
Instances
| DBSum Int16 Source # | |
Defined in Rel8.Type.Sum | |
| DBSum Int32 Source # | |
Defined in Rel8.Type.Sum | |
| DBSum Int64 Source # | |
Defined in Rel8.Type.Sum | |
| DBSum Scientific Source # | |
Defined in Rel8.Type.Sum | |
| DBSum CalendarDiffTime Source # | |
Defined in Rel8.Type.Sum | |
| DBSum Double Source # | |
Defined in Rel8.Type.Sum | |
| DBSum Float Source # | |
Defined in Rel8.Type.Sum | |
| PowerOf10 n => DBSum (Fixed n) Source # | |
Defined in Rel8.Type.Sum | |
sum :: (Sql DBNum a, Sql DBSum a) => Aggregator' fold (Expr a) (Expr a) Source #
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.
sumOn :: (Sql DBNum a, Sql DBSum a) => (i -> Expr a) -> Aggregator' fold i (Expr a) Source #
Applies sum to the column selected by the given fucntion.
sumWhere :: (Sql DBNum a, Sql DBSum a) => (i -> Expr Bool) -> (i -> Expr a) -> Aggregator' fold i (Expr a) Source #
sumWhere is a combination of filterWhere and sumOn.
avg :: Sql DBSum a => Aggregator1 (Expr a) (Expr a) Source #
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.
avgOn :: Sql DBSum a => (i -> Expr a) -> Aggregator1 i (Expr a) Source #
Applies avg to the column selected by the given fucntion.
class DBType a => DBString a Source #
The class of data types that support the string_agg() aggregation
function.
Instances
| DBString ByteString Source # | |
Defined in Rel8.Type.String | |
| DBString ByteString Source # | |
Defined in Rel8.Type.String | |
| DBString Text Source # | |
Defined in Rel8.Type.String | |
| DBString Text Source # | |
Defined in Rel8.Type.String | |
| DBString (CI Text) Source # | |
Defined in Rel8.Type.String | |
| DBString (CI Text) Source # | |
Defined in Rel8.Type.String | |
stringAgg :: (Sql IsString a, Sql DBString a) => Expr a -> Aggregator' fold (Expr a) (Expr a) Source #
Corresponds to string_agg().
count :: Aggregator' fold (Expr a) (Expr Int64) Source #
Count the occurances of a single column. Corresponds to COUNT(a)
countOn :: (i -> Expr a) -> Aggregator' fold i (Expr Int64) Source #
Applies count to the column selected by the given function.
countDistinct :: Sql DBEq a => Aggregator' fold (Expr a) (Expr Int64) Source #
Count the number of distinct occurrences of a single column. Corresponds to
COUNT(DISTINCT a)
countDistinctOn :: Sql DBEq a => (i -> Expr a) -> Aggregator' fold i (Expr Int64) Source #
Applies countDistinct to the column selected by the given function.
countWhere :: Aggregator' fold (Expr Bool) (Expr Int64) Source #
A count of the number of times a given expression is true.
countWhereOn :: (i -> Expr Bool) -> Aggregator' fold i (Expr Int64) Source #
Applies countWhere to the column selected by the given function.
andOn :: (i -> Expr Bool) -> Aggregator' fold i (Expr Bool) Source #
Applies and to the column selected by the given function.
orOn :: (i -> Expr Bool) -> Aggregator' fold i (Expr Bool) Source #
Applies or to the column selected by the given function.
aggregateFunction :: (Table Expr i, Sql DBType a) => QualifiedName -> Aggregator1 i (Expr a) Source #
aggregateFunction allows the use use of custom aggregation functions
or PostgreSQL aggregation functions which are not otherwise supported by
Rel8.
mode :: Sql DBOrd a => Aggregator1 (Expr a) (Expr a) Source #
Corresponds to mode() WITHIN GROUP (ORDER BY _).
modeOn :: Sql DBOrd a => (i -> Expr a) -> Aggregator1 i (Expr a) Source #
Applies mode to the column selected by the given function.
percentile :: Sql DBOrd a => Expr Double -> Aggregator1 (Expr a) (Expr a) Source #
Corresponds to percentile_disc(_) WITHIN GROUP (ORDER BY _).
percentileOn :: Sql DBOrd a => Expr Double -> (i -> Expr a) -> Aggregator1 i (Expr a) Source #
Applies percentile to the column selected by the given function.
percentileContinuous :: Sql DBFractional a => Expr Double -> Aggregator1 (Expr a) (Expr a) Source #
Corresponds to percentile_cont(_) WITHIN GROUP (ORDER BY _).
percentileContinuousOn :: Sql DBFractional a => Expr Double -> (i -> Expr a) -> Aggregator1 i (Expr a) Source #
Applies percentileContinuous to the column selected by the given
function.
hypotheticalRank :: Order a -> a -> Aggregator' fold a (Expr Int64) Source #
Corresponds to rank(_) WITHIN GROUP (ORDER BY _).
hypotheticalDenseRank :: Order a -> a -> Aggregator' fold a (Expr Int64) Source #
Corresponds to dense_rank(_) WITHIN GROUP (ORDER BY _).
hypotheticalPercentRank :: Order a -> a -> Aggregator' fold a (Expr Double) Source #
Corresponds to percent_rank(_) WITHIN GROUP (ORDER BY _).
hypotheticalCumeDist :: Order a -> a -> Aggregator' fold a (Expr Double) Source #
Corresponds to cume_dist(_) WITHIN GROUP (ORDER BY _).
Ordering
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.
nullsFirst :: Order (Expr a) -> Order (Expr (Maybe a)) Source #
Transform an ordering so that null values appear first. This corresponds
to NULLS FIRST in SQL.
nullsLast :: Order (Expr a) -> Order (Expr (Maybe a)) Source #
Transform an ordering so that null values appear first. This corresponds
to NULLS LAST in SQL.
Window functions
Window is an applicative functor that represents expressions that
contain
window functions.
window can be used to
evaluate these expressions over a particular query.
Instances
| ProductProfunctor Window Source # | |
| Profunctor Window Source # | |
Defined in Rel8.Window Methods dimap :: (a -> b) -> (c -> d) -> Window b c -> Window a d # lmap :: (a -> b) -> Window b c -> Window a c # rmap :: (b -> c) -> Window a b -> Window a c # (#.) :: forall a b c q. Coercible c b => q b c -> Window a b -> Window a c # (.#) :: forall a b c q. Coercible b a => Window b c -> q a b -> Window a c # | |
| Applicative (Window a) Source # | |
| Functor (Window a) Source # | |
| Apply (Window a) Source # | |
window :: Window a b -> Query a -> Query b Source #
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.
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 <>.
over :: Window a b -> Partition a -> Window a b infixl 1 Source #
over adds a Partition to a Window expression.
@@
@@cumulative (sum . salary) over partitionBy department <> orderPartitionBy (salary >$< desc)
partitionBy :: forall b a. EqTable b => (a -> b) -> Partition a Source #
Restricts a window function to operate only the group of rows that share the same value(s) for the given expression(s).
orderPartitionBy :: Order a -> Partition a Source #
Controls the order in which rows are processed by window functions. This does not need to match the ordering of the overall query.
cumulative :: Aggregator' fold i a -> Window i a Source #
cumulative allows the use of aggregation functions in Window
expressions. In particular,
(when combined with cumulative sumorderPartitionBy) gives a running total,
also known as a "cumulative sum", hence the name cumulative.
currentRow :: Window a a Source #
Return every column of the current row of a window query.
lag :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a) Source #
returns the row lag nn rows before the current row in a given
window. Returns nothingTable if n is out of bounds.
lagOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a) Source #
Applies lag to the columns selected by the given function.
lead :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a) Source #
returns the row lead nn rows after the current row in a given
window. Returns nothingTable if n is out of bounds.
leadOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a) Source #
Applies lead to the columns selected by the given function.
firstValue :: Table Expr a => Window a a Source #
firstValue returns the first row of the window of the current row.
firstValueOn :: Table Expr a => (i -> a) -> Window i a Source #
Applies firstValue to the columns selected by the given function.
lastValue :: Table Expr a => Window a a Source #
lastValue returns the first row of the window of the current row.
lastValueOn :: Table Expr a => (i -> a) -> Window i a Source #
Applies lastValue to the columns selected by the given function.
nthValue :: Table Expr a => Expr Int32 -> Window a (MaybeTable Expr a) Source #
returns the nthValue nnth row of the window of the current row.
Returns nothingTable if n is out of bounds.
nthValueOn :: Table Expr a => Expr Int32 -> (i -> a) -> Window i (MaybeTable Expr a) Source #
Applies nthValue to the columns selected by the given function.
indexed :: Query a -> Query (Expr Int64, a) Source #
Pair each row of a query with its index within the query.
Bindings
rebind :: Table Expr a => String -> a -> Query a Source #
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.
IO
class (ToExprs exprs a, a ~ FromExprs exprs) => Serializable exprs a | exprs -> a Source #
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.
Instances
| (ToExprs exprs a, a ~ FromExprs exprs) => Serializable exprs a Source # | |
Defined in Rel8.Table.Serialize | |
| Sql DBType a => Serializable (Expr a) a Source # | |
Defined in Rel8.Table.Serialize | |
class Table Expr exprs => ToExprs exprs a Source #
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.
Instances
| (Sql DBType a, x ~ Expr a) => ToExprs x a Source # | |
Defined in Rel8.Table.Serialize | |
| (Rel8able t', t' ~ Choose (Algebra t) t, x ~ t' Expr, result ~ Result) => ToExprs x (t result) Source # | |
Defined in Rel8.Table.Rel8able | |
| (ToExprs exprs1 a, ToExprs exprs2 b, x ~ EitherTable Expr exprs1 exprs2) => ToExprs x (Either a b) Source # | |
Defined in Rel8.Table.Either | |
| (ToExprs exprs1 a, ToExprs exprs2 b, x ~ TheseTable Expr exprs1 exprs2) => ToExprs x (These a b) Source # | |
Defined in Rel8.Table.These | |
| (ToExprs exprs1 a, ToExprs exprs2 b, x ~ (exprs1, exprs2)) => ToExprs x (a, b) Source # | |
Defined in Rel8.Table.Serialize | |
| (ToExprs exprs1 a, ToExprs exprs2 b, ToExprs exprs3 c, x ~ (exprs1, exprs2, exprs3)) => ToExprs x (a, b, c) Source # | |
Defined in Rel8.Table.Serialize | |
| (ToExprs exprs1 a, ToExprs exprs2 b, ToExprs exprs3 c, ToExprs exprs4 d, x ~ (exprs1, exprs2, exprs3, exprs4)) => ToExprs x (a, b, c, d) Source # | |
Defined in Rel8.Table.Serialize | |
| (ToExprs exprs1 a, ToExprs exprs2 b, ToExprs exprs3 c, ToExprs exprs4 d, ToExprs exprs5 e, x ~ (exprs1, exprs2, exprs3, exprs4, exprs5)) => ToExprs x (a, b, c, d, e) Source # | |
Defined in Rel8.Table.Serialize | |
| (ToExprs exprs1 a, ToExprs exprs2 b, ToExprs exprs3 c, ToExprs exprs4 d, ToExprs exprs5 e, ToExprs exprs6 f, x ~ (exprs1, exprs2, exprs3, exprs4, exprs5, exprs6)) => ToExprs x (a, b, c, d, e, f) Source # | |
Defined in Rel8.Table.Serialize | |
| (ToExprs exprs1 a, ToExprs exprs2 b, ToExprs exprs3 c, ToExprs exprs4 d, ToExprs exprs5 e, ToExprs exprs6 f, ToExprs exprs7 g, x ~ (exprs1, exprs2, exprs3, exprs4, exprs5, exprs6, exprs7)) => ToExprs x (a, b, c, d, e, f, g) Source # | |
Defined in Rel8.Table.Serialize | |
| (Sql DBType a, NotNull a, x ~ NonEmpty a) => ToExprs (Expr x) (NonEmpty a) Source # | |
Defined in Rel8.Table.Serialize | |
| (Sql DBType a, NotNull a, x ~ Maybe a) => ToExprs (Expr x) (Maybe a) Source # | |
Defined in Rel8.Table.Serialize | |
| (Sql DBType a, x ~ [a]) => ToExprs (Expr x) [a] Source # | |
Defined in Rel8.Table.Serialize | |
| (ToExprs exprs a, context ~ Expr) => ToExprs (ListTable context exprs) [a] Source # | |
Defined in Rel8.Table.List | |
| (ToExprs exprs a, context ~ Expr) => ToExprs (MaybeTable context exprs) (Maybe a) Source # | |
Defined in Rel8.Table.Maybe | |
| (ToExprs exprs a, context ~ Expr) => ToExprs (NonEmptyTable context exprs) (NonEmpty a) Source # | |
Defined in Rel8.Table.NonEmpty | |
| (ToExprs exprs a, context ~ Expr) => ToExprs (NullTable context exprs) (Maybe a) Source # | |
Defined in Rel8.Table.Null | |
type Result = Identity Source #
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.
Running statements
To run queries and otherwise interact with a PostgreSQL database, Rel8
provides the run functions. These produce a Statements
which can be passed to statement to execute the statement
against a PostgreSQL Connection.
run takes a Statement, which can be constructed using either select,
insert, update or delete. It decodes the rows returned by the
statement as a list of Haskell of values. See run_, runN, run1,
runMaybe and runVector for other variations.
Note that constructing an Insert, Update or Delete will require the
DisambiguateRecordFields language extension to be enabled.
runN :: Statement () -> Statement () Int64 Source #
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).
SELECT
INSERT
The constituent parts of a SQL INSERT statement.
Constructors
| Insert | |
Fields
| |
data OnConflict names Source #
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 Upsert names where Source #
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.
Constructors
| Upsert | |
Fields
| |
unsafeDefault :: Expr a Source #
Corresponds to the SQL DEFAULT expression.
This Expr is unsafe for numerous reasons, and should be used with care:
- This
Expronly makes sense in anINSERTorUPDATEstatement. - Rel8 is not able to verify that a particular column actually has a
DEFAULTvalue. Trying to useunsafeDefaultwhere there is no default will cause a runtime crash DEFAULTvalues can not be transformed. For example, the innocuous Rel8 codeunsafeDefault + 1will crash, despite type checking.
Also note, PostgreSQL's syntax rules mean that DEFAULT can only appear in
INSERT expressions whose rows are specified using VALUES. This means
that if the rows field of your 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.
showInsert :: Insert a -> String Source #
DELETE
The constituent parts of a DELETE statement.
Constructors
| Delete | |
Fields
| |
showDelete :: Delete a -> String Source #
UPDATE
The constituent parts of an UPDATE statement.
Constructors
| Update | |
Fields
| |
showUpdate :: Update a -> String Source #
.. RETURNING
data Returning names a where Source #
Constructors
| NoReturning :: Returning names () | No |
| Returning :: (Selects names exprs, Table Expr a) => (exprs -> a) -> Returning names (Query a) |
|
WITH
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
}
showStatement :: Statement a -> String Source #
CREATE VIEW
createView :: Selects names exprs => TableSchema names -> Query exprs -> Statement () () Source #
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.
createOrReplaceView :: Selects names exprs => TableSchema names -> Query exprs -> Statement () () Source #
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.