Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Expression.Inline
Contents
Description
inline expressions
Synopsis
- class Inline x where
- class InlineParam x ty where
- inlineParam :: x -> Expr ty
- class InlineField (field :: (Symbol, Type)) (fieldpg :: (Symbol, NullType)) where
- inlineField :: P field -> Aliased (Expression grp lat with db params from) fieldpg
- inlineFields :: (IsRecord hask fields, AllZip InlineField fields row) => hask -> NP (Aliased (Expression Ungrouped '[] with db params '[])) row
- class InlineColumn (field :: (Symbol, Type)) (column :: (Symbol, ColumnType)) where
- inlineColumn :: P field -> Aliased (Optional (Expression grp lat with db params from)) column
- inlineColumns :: (IsRecord hask xs, AllZip InlineColumn xs columns) => hask -> NP (Aliased (Optional (Expression Ungrouped '[] with db params '[]))) columns
Inline
The Inline
class allows embedding a Haskell value directly
as an Expression
using inline
.
>>>
printSQL (inline 'a')
(E'a' :: char(1))
>>>
printSQL (inline (1 :: Double))
(1.0 :: float8)
>>>
printSQL (inline (Json ([1, 2] :: [Double])))
('[1.0,2.0]' :: json)
>>>
printSQL (inline (Enumerated GT))
'GT'
Instances
class InlineParam x ty where Source #
Methods
inlineParam :: x -> Expr ty Source #
Instances
(Inline x, pg ~ PG x) => InlineParam x (NotNull pg) Source # | |
Defined in Squeal.PostgreSQL.Expression.Inline Methods inlineParam :: x -> Expr (NotNull pg) Source # | |
(Inline x, pg ~ PG x) => InlineParam (Maybe x) (Null pg) Source # | |
Defined in Squeal.PostgreSQL.Expression.Inline |
class InlineField (field :: (Symbol, Type)) (fieldpg :: (Symbol, NullType)) where Source #
Lifts Inline
to fields.
Methods
inlineField :: P field -> Aliased (Expression grp lat with db params from) fieldpg Source #
Instances
(KnownSymbol alias, InlineParam x ty) => InlineField (alias ::: x) (alias ::: ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Inline Methods inlineField :: P (alias ::: x) -> Aliased (Expression grp lat with db params from) (alias ::: ty) Source # |
Arguments
:: (IsRecord hask fields, AllZip InlineField fields row) | |
=> hask | record |
-> NP (Aliased (Expression Ungrouped '[] with db params '[])) row |
Use a Haskell record as a inline a row of expressions.
class InlineColumn (field :: (Symbol, Type)) (column :: (Symbol, ColumnType)) where Source #
Lifts Inline
to a column entry
Methods
inlineColumn :: P field -> Aliased (Optional (Expression grp lat with db params from)) column Source #
Haskell record field as a inline column
Instances
(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: Optional I (Def :=> x)) (col ::: (Def :=> ty)) Source # | |
(KnownSymbol col, InlineParam x ty) => InlineColumn (col ::: x) (col ::: (NoDef :=> ty)) Source # | |
Defined in Squeal.PostgreSQL.Expression.Inline |
Arguments
:: (IsRecord hask xs, AllZip InlineColumn xs columns) | |
=> hask | record |
-> NP (Aliased (Optional (Expression Ungrouped '[] with db params '[]))) columns |
Use a Haskell record as a inline list of columns