Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Alias = Text
- type Depth = Integer
- data EmbedParam
- type EmbedPath = [Text]
- type Field = (FieldName, JsonPath)
- data Filter = Filter {}
- type Hint = Text
- data CallQuery = FunctionCall {}
- data CallParams
- type CallRequest = CallQuery
- data JoinCondition = JoinCondition (QualifiedIdentifier, FieldName) (QualifiedIdentifier, FieldName)
- data JoinType
- data JsonOperand
- data JsonOperation
- = JArrow {
- jOp :: JsonOperand
- | J2Arrow {
- jOp :: JsonOperand
- = JArrow {
- type JsonPath = [JsonOperation]
- type ListVal = [Text]
- data LogicOperator
- data LogicTree
- data MutateQuery
- = Insert {
- in_ :: QualifiedIdentifier
- insCols :: Set FieldName
- insBody :: Maybe ByteString
- onConflict :: Maybe (PreferResolution, [FieldName])
- where_ :: [LogicTree]
- returning :: [FieldName]
- | Update { }
- | Delete { }
- = Insert {
- type MutateRequest = MutateQuery
- type NodeName = Text
- data OpExpr = OpExpr Bool Operation
- data Operation
- data OrderDirection
- data OrderNulls
- data OrderTerm = OrderTerm {}
- type ReadNode = (ReadQuery, (NodeName, Maybe Relationship, Maybe Alias, Maybe Hint, Maybe JoinType, Depth))
- data ReadQuery = Select {
- select :: [SelectItem]
- from :: QualifiedIdentifier
- fromAlias :: Maybe Alias
- implicitJoins :: [QualifiedIdentifier]
- where_ :: [LogicTree]
- joinConditions :: [JoinCondition]
- order :: [OrderTerm]
- range_ :: NonnegRange
- type ReadRequest = Tree ReadNode
- type SelectItem = (Field, Maybe Cast, Maybe Alias, Maybe Hint, Maybe JoinType)
- type SingleVal = Text
- data TrileanVal
- = TriTrue
- | TriFalse
- | TriNull
- | TriUnknown
- fstFieldNames :: ReadRequest -> [FieldName]
Documentation
data EmbedParam Source #
EPHint Hint | Disambiguates an embedding operation when there's multiple relationships between two tables. Can be the name of a foreign key constraint, column name or the junction in an m2m relationship. |
EPJoinType JoinType |
type EmbedPath = [Text] Source #
Path of the embedded levels, e.g "clients.projects.name=eq.." gives Path ["clients", "projects"]
data CallParams Source #
KeyParams [ProcParam] | Call with key params: func(a := val1, b:= val2) |
OnePosParam ProcParam | Call with positional params(only one supported): func(val) |
type CallRequest = CallQuery Source #
data JoinCondition Source #
Instances
Eq JoinCondition Source # | |
Defined in PostgREST.Request.Types (==) :: JoinCondition -> JoinCondition -> Bool # (/=) :: JoinCondition -> JoinCondition -> Bool # |
data JsonOperand Source #
Represents the key(->
key'`) or index(->
1`::int`), the index is Text
because we reuse our escaping functons and let pg do the casting with
'1'::int
Instances
Eq JsonOperand Source # | |
Defined in PostgREST.Request.Types (==) :: JsonOperand -> JsonOperand -> Bool # (/=) :: JsonOperand -> JsonOperand -> Bool # |
data JsonOperation Source #
Represents the single arrow ->
or double arrow ->>
operators
JArrow | |
| |
J2Arrow | |
|
Instances
Eq JsonOperation Source # | |
Defined in PostgREST.Request.Types (==) :: JsonOperation -> JsonOperation -> Bool # (/=) :: JsonOperation -> JsonOperation -> Bool # |
type JsonPath = [JsonOperation] Source #
Json path operations as specified in https://www.postgresql.org/docs/current/static/functions-json.html
data LogicOperator Source #
Instances
Eq LogicOperator Source # | |
Defined in PostgREST.Request.Types (==) :: LogicOperator -> LogicOperator -> Bool # (/=) :: LogicOperator -> LogicOperator -> Bool # |
Boolean logic expression tree e.g. "and(name.eq.N,or(id.eq.1,id.eq.2))" is:
And / name.eq.N Or / id.eq.1 id.eq.2
data MutateQuery Source #
Insert | |
| |
Update | |
Delete | |
type MutateRequest = MutateQuery Source #
data OrderDirection Source #
Instances
Eq OrderDirection Source # | |
Defined in PostgREST.Request.Types (==) :: OrderDirection -> OrderDirection -> Bool # (/=) :: OrderDirection -> OrderDirection -> Bool # |
data OrderNulls Source #
Instances
Eq OrderNulls Source # | |
Defined in PostgREST.Request.Types (==) :: OrderNulls -> OrderNulls -> Bool # (/=) :: OrderNulls -> OrderNulls -> Bool # |
type ReadNode = (ReadQuery, (NodeName, Maybe Relationship, Maybe Alias, Maybe Hint, Maybe JoinType, Depth)) Source #
Select | |
|
type ReadRequest = Tree ReadNode Source #
type SelectItem = (Field, Maybe Cast, Maybe Alias, Maybe Hint, Maybe JoinType) Source #
The select value in `/tbl?select=alias:field::cast`
data TrileanVal Source #
Three-valued logic values
Instances
Eq TrileanVal Source # | |
Defined in PostgREST.Request.Types (==) :: TrileanVal -> TrileanVal -> Bool # (/=) :: TrileanVal -> TrileanVal -> Bool # |
fstFieldNames :: ReadRequest -> [FieldName] Source #