postgrest-7.0.1: REST API for any Postgres database

Safe HaskellNone
LanguageHaskell2010

PostgREST.Types

Description

 
Synopsis

Documentation

data ContentType Source #

Enumeration of currently supported response content types

Instances
Eq ContentType Source # 
Instance details

Defined in PostgREST.Types

Show ContentType Source # 
Instance details

Defined in PostgREST.Types

toHeader :: ContentType -> Header Source #

Convert from ContentType to a full HTTP Header

toMime :: ContentType -> ByteString Source #

Convert from ContentType to a ByteString representing the mime type

decodeContentType :: ByteString -> ContentType Source #

Convert from ByteString to ContentType. Warning: discards MIME parameters

type SqlQuery = Text Source #

A SQL query that can be executed independently

type SqlFragment = Text Source #

A part of a SQL query that cannot be executed independently

data PreferRepresentation Source #

How to return the mutated data. From https://tools.ietf.org/html/rfc7240#section-4.2

Constructors

Full

Return the body plus the Location header(in case of POST).

HeadersOnly

Return the Location header(in case of POST). This needs a SELECT privilege on the pk.

None

Return nothing from the mutated data.

data PreferParameters Source #

Constructors

SingleObject

Pass all parameters as a single json object to a stored procedure

MultipleObjects

Pass an array of json objects as params to a stored procedure

data PreferCount Source #

Constructors

ExactCount

exact count(slower)

PlannedCount

PostgreSQL query planner rows count guess. Done by using EXPLAIN {query}.

EstimatedCount

use the query planner rows if the count is superior to max-rows, otherwise get the exact count.

Instances
Eq PreferCount Source # 
Instance details

Defined in PostgREST.Types

Show PreferCount Source # 
Instance details

Defined in PostgREST.Types

data PgArg Source #

Constructors

PgArg 

Fields

Instances
Eq PgArg Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: PgArg -> PgArg -> Bool #

(/=) :: PgArg -> PgArg -> Bool #

Ord PgArg Source # 
Instance details

Defined in PostgREST.Types

Methods

compare :: PgArg -> PgArg -> Ordering #

(<) :: PgArg -> PgArg -> Bool #

(<=) :: PgArg -> PgArg -> Bool #

(>) :: PgArg -> PgArg -> Bool #

(>=) :: PgArg -> PgArg -> Bool #

max :: PgArg -> PgArg -> PgArg #

min :: PgArg -> PgArg -> PgArg #

Show PgArg Source # 
Instance details

Defined in PostgREST.Types

Methods

showsPrec :: Int -> PgArg -> ShowS #

show :: PgArg -> String #

showList :: [PgArg] -> ShowS #

data PgType Source #

Instances
Eq PgType Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: PgType -> PgType -> Bool #

(/=) :: PgType -> PgType -> Bool #

Ord PgType Source # 
Instance details

Defined in PostgREST.Types

Show PgType Source # 
Instance details

Defined in PostgREST.Types

data RetType Source #

Constructors

Single PgType 
SetOf PgType 
Instances
Eq RetType Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: RetType -> RetType -> Bool #

(/=) :: RetType -> RetType -> Bool #

Ord RetType Source # 
Instance details

Defined in PostgREST.Types

Show RetType Source # 
Instance details

Defined in PostgREST.Types

type ProcsMap = HashMap QualifiedIdentifier [ProcDescription] Source #

A map of all procs, all of which can be overloaded(one entry will have more than one ProcDescription). | It uses a HashMap for a faster lookup.

findProc :: QualifiedIdentifier -> Set Text -> Bool -> ProcsMap -> Maybe ProcDescription Source #

Search a pg procedure by its parameters. Since a function can be overloaded, the name is not enough to find it. An overloaded function can have a different volatility or even a different return type. Ideally, handling overloaded functions should be left to pg itself. But we need to know certain proc attributes in advance.

specifiedProcArgs :: Set FieldName -> Maybe ProcDescription -> [PgArg] Source #

Search the procedure parameters by matching them with the specified keys. If the key doesn't match a parameter, a parameter with a default type "text" is assumed.

data Table Source #

Instances
Eq Table Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: Table -> Table -> Bool #

(/=) :: Table -> Table -> Bool #

Ord Table Source # 
Instance details

Defined in PostgREST.Types

Methods

compare :: Table -> Table -> Ordering #

(<) :: Table -> Table -> Bool #

(<=) :: Table -> Table -> Bool #

(>) :: Table -> Table -> Bool #

(>=) :: Table -> Table -> Bool #

max :: Table -> Table -> Table #

min :: Table -> Table -> Table #

Show Table Source # 
Instance details

Defined in PostgREST.Types

Methods

showsPrec :: Int -> Table -> ShowS #

show :: Table -> String #

showList :: [Table] -> ShowS #

data Column Source #

Instances
Eq Column Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: Column -> Column -> Bool #

(/=) :: Column -> Column -> Bool #

Ord Column Source # 
Instance details

Defined in PostgREST.Types

Show Column Source # 
Instance details

Defined in PostgREST.Types

type SourceColumn = (Column, ViewColumn) Source #

The source table column a view column refers to

data PrimaryKey Source #

Constructors

PrimaryKey 

Fields

Instances
Eq PrimaryKey Source # 
Instance details

Defined in PostgREST.Types

Show PrimaryKey Source # 
Instance details

Defined in PostgREST.Types

data OrderNulls Source #

Instances
Eq OrderNulls Source # 
Instance details

Defined in PostgREST.Types

Show OrderNulls Source # 
Instance details

Defined in PostgREST.Types

data OrderTerm Source #

Instances
Eq OrderTerm Source # 
Instance details

Defined in PostgREST.Types

Show OrderTerm Source # 
Instance details

Defined in PostgREST.Types

data QualifiedIdentifier Source #

Represents a pg identifier with a prepended schema name "schema.table" When qiSchema is "", the schema is defined by the pg search_path

Constructors

QualifiedIdentifier 
Instances
Eq QualifiedIdentifier Source # 
Instance details

Defined in PostgREST.Types

Ord QualifiedIdentifier Source # 
Instance details

Defined in PostgREST.Types

Show QualifiedIdentifier Source # 
Instance details

Defined in PostgREST.Types

Generic QualifiedIdentifier Source # 
Instance details

Defined in PostgREST.Types

Associated Types

type Rep QualifiedIdentifier :: Type -> Type #

Hashable QualifiedIdentifier Source # 
Instance details

Defined in PostgREST.Types

type Rep QualifiedIdentifier Source # 
Instance details

Defined in PostgREST.Types

type Rep QualifiedIdentifier = D1 (MetaData "QualifiedIdentifier" "PostgREST.Types" "postgrest-7.0.1-I2LxYwBzonR6GboyH3n0YA" False) (C1 (MetaCons "QualifiedIdentifier" PrefixI True) (S1 (MetaSel (Just "qiSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Schema) :*: S1 (MetaSel (Just "qiName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TableName)))

data Cardinality Source #

The relationship cardinality). | TODO: missing one-to-one

Constructors

O2M

one-to-many, previously known as Parent

M2O

many-to-one, previously known as Child

M2M

many-to-many, previously known as Many

Instances
Eq Cardinality Source # 
Instance details

Defined in PostgREST.Types

Show Cardinality Source # 
Instance details

Defined in PostgREST.Types

data Relation Source #

Relationship between two tables. The order of the relColumns and relFColumns should be maintained to get the join conditions right. TODO merge relColumns and relFColumns to a tuple or Data.Bimap

Constructors

Relation 

Fields

Instances
Eq Relation Source # 
Instance details

Defined in PostgREST.Types

Show Relation Source # 
Instance details

Defined in PostgREST.Types

data Junction Source #

Junction table on an M2M relationship

Instances
Eq Junction Source # 
Instance details

Defined in PostgREST.Types

Show Junction Source # 
Instance details

Defined in PostgREST.Types

data PayloadJSON Source #

Constructors

ProcessedJSON

Cached attributes of a JSON payload

Fields

  • pjRaw :: ByteString

    This is the raw ByteString that comes from the request body. We cache this instead of an Aeson Value because it was detected that for large payloads the encoding had high memory usage, see https://github.com/PostgREST/postgrest/pull/1005 for more details

  • pjKeys :: Set Text

    Keys of the object or if it's an array these keys are guaranteed to be the same across all its objects

RawJSON 

Fields

Instances
Eq PayloadJSON Source # 
Instance details

Defined in PostgREST.Types

Show PayloadJSON Source # 
Instance details

Defined in PostgREST.Types

data PJType Source #

Constructors

PJArray 

Fields

PJObject 
Instances
Eq PJType Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: PJType -> PJType -> Bool #

(/=) :: PJType -> PJType -> Bool #

Show PJType Source # 
Instance details

Defined in PostgREST.Types

data Proxy Source #

Constructors

Proxy 
Instances
Eq Proxy Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: Proxy -> Proxy -> Bool #

(/=) :: Proxy -> Proxy -> Bool #

Show Proxy Source # 
Instance details

Defined in PostgREST.Types

Methods

showsPrec :: Int -> Proxy -> ShowS #

show :: Proxy -> String #

showList :: [Proxy] -> ShowS #

data OpExpr Source #

Constructors

OpExpr Bool Operation 
Instances
Eq OpExpr Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: OpExpr -> OpExpr -> Bool #

(/=) :: OpExpr -> OpExpr -> Bool #

Show OpExpr Source # 
Instance details

Defined in PostgREST.Types

data Operation Source #

Instances
Eq Operation Source # 
Instance details

Defined in PostgREST.Types

Show Operation Source # 
Instance details

Defined in PostgREST.Types

type SingleVal = Text Source #

Represents a single value in a filter, e.g. id=eq.singleval

type ListVal = [Text] Source #

Represents a list value in a filter, e.g. id=in.(val1,val2,val3)

data LogicOperator Source #

Constructors

And 
Or 

data LogicTree Source #

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

Instances
Eq LogicTree Source # 
Instance details

Defined in PostgREST.Types

Show LogicTree Source # 
Instance details

Defined in PostgREST.Types

data JsonOperation Source #

Represents the single arrow `->` or double arrow ->> operators

Constructors

JArrow 

Fields

J2Arrow 

Fields

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

Constructors

JKey 

Fields

JIdx 

Fields

Instances
Eq JsonOperand Source # 
Instance details

Defined in PostgREST.Types

Show JsonOperand Source # 
Instance details

Defined in PostgREST.Types

type Cast = Text Source #

newtype GucHeader Source #

Custom guc header, it's obtained by parsing the json in a: `SET LOCAL "response.headers" = '[{"Set-Cookie": ".."}]'

Instances
Eq GucHeader Source # 
Instance details

Defined in PostgREST.Types

Show GucHeader Source # 
Instance details

Defined in PostgREST.Types

FromJSON GucHeader Source # 
Instance details

Defined in PostgREST.Types

addHeadersIfNotIncluded :: [Header] -> [Header] -> [Header] Source #

Add headers not already included to allow the user to override them instead of duplicating them

type SelectItem = (Field, Maybe Cast, Maybe Alias, Maybe EmbedHint) Source #

This type will hold information about which particular Relation between two tables to choose when there are multiple ones. Specifically, it will contain the name of the foreign key or the join table in many to many relations.

type EmbedHint = Text Source #

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.

type EmbedPath = [Text] Source #

Path of the embedded levels, e.g "clients.projects.name=eq.." gives Path ["clients", "projects"]

data Filter Source #

Constructors

Filter 

Fields

Instances
Eq Filter Source # 
Instance details

Defined in PostgREST.Types

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

Show Filter Source # 
Instance details

Defined in PostgREST.Types

data ReadQuery Source #

Constructors

Select 

Fields

Instances
Eq ReadQuery Source # 
Instance details

Defined in PostgREST.Types

Show ReadQuery Source # 
Instance details

Defined in PostgREST.Types

data PgVersion Source #

Constructors

PgVersion 

Fields

minimumPgVersion :: PgVersion Source #

Tells the minimum PostgreSQL version required by this version of PostgREST

type JSPath = [JSPathExp] Source #

full jspath, e.g. .property[0].attr.detail

data JSPathExp Source #

jspath expression, e.g. .property, .property[0] or ."property-dash"

Constructors

JSPKey Text 
JSPIdx Int 
Instances
Eq JSPathExp Source # 
Instance details

Defined in PostgREST.Types

Show JSPathExp Source # 
Instance details

Defined in PostgREST.Types

data ConnectionStatus Source #

Current database connection status data ConnectionStatus