| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
PostgREST.Types
Description
Synopsis
- data ContentType
- toHeader :: ContentType -> Header
- toMime :: ContentType -> ByteString
- decodeContentType :: ByteString -> ContentType
- data PreferResolution
- data DbStructure = DbStructure {
- dbTables :: [Table]
- dbColumns :: [Column]
- dbRelations :: [Relation]
- dbPrimaryKeys :: [PrimaryKey]
- dbProcs :: HashMap Text [ProcDescription]
- pgVersion :: PgVersion
- tableCols :: DbStructure -> Schema -> TableName -> [Column]
- tablePKCols :: DbStructure -> Schema -> TableName -> [Text]
- data PgArg = PgArg {}
- data PgType
- data RetType
- data ProcVolatility
- data ProcDescription = ProcDescription {
- pdName :: Text
- pdDescription :: Maybe Text
- pdArgs :: [PgArg]
- pdReturnType :: RetType
- pdVolatility :: ProcVolatility
- findProc :: QualifiedIdentifier -> Set Text -> Bool -> HashMap Text [ProcDescription] -> Maybe ProcDescription
- specifiedProcArgs :: Set FieldName -> Maybe ProcDescription -> [PgArg]
- type Schema = Text
- type TableName = Text
- type SqlQuery = Text
- type SqlFragment = Text
- data Table = Table {}
- newtype ForeignKey = ForeignKey {}
- data Column = Column {
- colTable :: Table
- colName :: FieldName
- colDescription :: Maybe Text
- colPosition :: Int32
- colNullable :: Bool
- colType :: Text
- colUpdatable :: Bool
- colMaxLen :: Maybe Int32
- colPrecision :: Maybe Int32
- colDefault :: Maybe Text
- colEnum :: [Text]
- colFK :: Maybe ForeignKey
- type Synonym = (Column, ViewColumn)
- type ViewColumn = Column
- data PrimaryKey = PrimaryKey {}
- data OrderDirection
- data OrderNulls
- data OrderTerm = OrderTerm {}
- data QualifiedIdentifier = QualifiedIdentifier {}
- data RelationType
- data Relation = Relation {
- relTable :: Table
- relColumns :: [Column]
- relFTable :: Table
- relFColumns :: [Column]
- relType :: RelationType
- relLinkTable :: Maybe Table
- relLinkCols1 :: Maybe [Column]
- relLinkCols2 :: Maybe [Column]
- isSelfJoin :: Relation -> Bool
- data PayloadJSON
- = ProcessedJSON { }
- | RawJSON {
- pjRaw :: ByteString
- data PJType
- data Proxy = Proxy {}
- type Operator = Text
- operators :: HashMap Operator SqlFragment
- ftsOperators :: HashMap Operator SqlFragment
- data OpExpr = OpExpr Bool Operation
- data Operation
- type Language = Text
- type SingleVal = Text
- type ListVal = [Text]
- data LogicOperator
- data LogicTree
- type FieldName = Text
- type JsonPath = [JsonOperation]
- data JsonOperation
- = JArrow {
- jOp :: JsonOperand
- | J2Arrow {
- jOp :: JsonOperand
- = JArrow {
- data JsonOperand
- type Field = (FieldName, JsonPath)
- type Alias = Text
- type Cast = Text
- type NodeName = Text
- type RpcQParam = (Text, Text)
- newtype GucHeader = GucHeader (Text, Text)
- toHeaders :: [GucHeader] -> [Header]
- type RelationDetail = Text
- type SelectItem = (Field, Maybe Cast, Maybe Alias, Maybe RelationDetail)
- type EmbedPath = [Text]
- data Filter = Filter {}
- data JoinCondition = JoinCondition (QualifiedIdentifier, FieldName) (QualifiedIdentifier, FieldName)
- data ReadQuery = Select {
- select :: [SelectItem]
- from :: TableName
- fromAlias :: Maybe Alias
- implicitJoins :: [TableName]
- where_ :: [LogicTree]
- joinConditions :: [JoinCondition]
- order :: [OrderTerm]
- range_ :: NonnegRange
- data MutateQuery
- data DbRequest
- type ReadRequest = Tree ReadNode
- type ReadNode = (ReadQuery, (NodeName, Maybe Relation, Maybe Alias, Maybe RelationDetail, Depth))
- type Depth = Integer
- type MutateRequest = MutateQuery
- data PgVersion = PgVersion {}
- minimumPgVersion :: PgVersion
- pgVersion94 :: PgVersion
- pgVersion95 :: PgVersion
- pgVersion96 :: PgVersion
- pgVersion100 :: PgVersion
- pgVersion109 :: PgVersion
- pgVersion110 :: PgVersion
- pgVersion112 :: PgVersion
- pgVersion114 :: PgVersion
- sourceCTEName :: SqlFragment
- type JSPath = [JSPathExp]
- data JSPathExp
- data ConnectionStatus
Documentation
data ContentType Source #
Enumeration of currently supported response content types
Constructors
| CTApplicationJSON | |
| CTSingularJSON | |
| CTTextCSV | |
| CTTextPlain | |
| CTOpenAPI | |
| CTOctetStream | |
| CTAny | |
| CTOther ByteString |
Instances
| Eq ContentType Source # | |
Defined in PostgREST.Types | |
| Show ContentType Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> ContentType -> ShowS # show :: ContentType -> String # showList :: [ContentType] -> ShowS # | |
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
data PreferResolution Source #
Constructors
| MergeDuplicates | |
| IgnoreDuplicates |
Instances
| Eq PreferResolution Source # | |
Defined in PostgREST.Types Methods (==) :: PreferResolution -> PreferResolution -> Bool # (/=) :: PreferResolution -> PreferResolution -> Bool # | |
| Show PreferResolution Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> PreferResolution -> ShowS # show :: PreferResolution -> String # showList :: [PreferResolution] -> ShowS # | |
data DbStructure Source #
Constructors
| DbStructure | |
Fields
| |
Instances
| Eq DbStructure Source # | |
Defined in PostgREST.Types | |
| Show DbStructure Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> DbStructure -> ShowS # show :: DbStructure -> String # showList :: [DbStructure] -> ShowS # | |
tablePKCols :: DbStructure -> Schema -> TableName -> [Text] Source #
Constructors
| Scalar QualifiedIdentifier | |
| Composite QualifiedIdentifier |
data ProcVolatility Source #
Instances
| Eq ProcVolatility Source # | |
Defined in PostgREST.Types Methods (==) :: ProcVolatility -> ProcVolatility -> Bool # (/=) :: ProcVolatility -> ProcVolatility -> Bool # | |
| Ord ProcVolatility Source # | |
Defined in PostgREST.Types Methods compare :: ProcVolatility -> ProcVolatility -> Ordering # (<) :: ProcVolatility -> ProcVolatility -> Bool # (<=) :: ProcVolatility -> ProcVolatility -> Bool # (>) :: ProcVolatility -> ProcVolatility -> Bool # (>=) :: ProcVolatility -> ProcVolatility -> Bool # max :: ProcVolatility -> ProcVolatility -> ProcVolatility # min :: ProcVolatility -> ProcVolatility -> ProcVolatility # | |
| Show ProcVolatility Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> ProcVolatility -> ShowS # show :: ProcVolatility -> String # showList :: [ProcVolatility] -> ShowS # | |
data ProcDescription Source #
Constructors
| ProcDescription | |
Fields
| |
Instances
| Eq ProcDescription Source # | |
Defined in PostgREST.Types Methods (==) :: ProcDescription -> ProcDescription -> Bool # (/=) :: ProcDescription -> ProcDescription -> Bool # | |
| Ord ProcDescription Source # | |
Defined in PostgREST.Types Methods compare :: ProcDescription -> ProcDescription -> Ordering # (<) :: ProcDescription -> ProcDescription -> Bool # (<=) :: ProcDescription -> ProcDescription -> Bool # (>) :: ProcDescription -> ProcDescription -> Bool # (>=) :: ProcDescription -> ProcDescription -> Bool # max :: ProcDescription -> ProcDescription -> ProcDescription # min :: ProcDescription -> ProcDescription -> ProcDescription # | |
| Show ProcDescription Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> ProcDescription -> ShowS # show :: ProcDescription -> String # showList :: [ProcDescription] -> ShowS # | |
findProc :: QualifiedIdentifier -> Set Text -> Bool -> HashMap Text [ProcDescription] -> 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.
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.
type SqlFragment = Text Source #
Constructors
| Table | |
Fields
| |
newtype ForeignKey Source #
Constructors
| ForeignKey | |
Instances
| Eq ForeignKey Source # | |
Defined in PostgREST.Types | |
| Ord ForeignKey Source # | |
Defined in PostgREST.Types Methods compare :: ForeignKey -> ForeignKey -> Ordering # (<) :: ForeignKey -> ForeignKey -> Bool # (<=) :: ForeignKey -> ForeignKey -> Bool # (>) :: ForeignKey -> ForeignKey -> Bool # (>=) :: ForeignKey -> ForeignKey -> Bool # max :: ForeignKey -> ForeignKey -> ForeignKey # min :: ForeignKey -> ForeignKey -> ForeignKey # | |
| Show ForeignKey Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> ForeignKey -> ShowS # show :: ForeignKey -> String # showList :: [ForeignKey] -> ShowS # | |
Constructors
| Column | |
Fields
| |
type Synonym = (Column, ViewColumn) Source #
A view column that refers to a table column
type ViewColumn = Column Source #
data PrimaryKey Source #
Constructors
| PrimaryKey | |
Instances
| Eq PrimaryKey Source # | |
Defined in PostgREST.Types | |
| Show PrimaryKey Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> PrimaryKey -> ShowS # show :: PrimaryKey -> String # showList :: [PrimaryKey] -> ShowS # | |
data OrderDirection Source #
Instances
| Eq OrderDirection Source # | |
Defined in PostgREST.Types Methods (==) :: OrderDirection -> OrderDirection -> Bool # (/=) :: OrderDirection -> OrderDirection -> Bool # | |
| Show OrderDirection Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> OrderDirection -> ShowS # show :: OrderDirection -> String # showList :: [OrderDirection] -> ShowS # | |
data OrderNulls Source #
Constructors
| OrderNullsFirst | |
| OrderNullsLast |
Instances
| Eq OrderNulls Source # | |
Defined in PostgREST.Types | |
| Show OrderNulls Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> OrderNulls -> ShowS # show :: OrderNulls -> String # showList :: [OrderNulls] -> ShowS # | |
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 # | |
Defined in PostgREST.Types Methods (==) :: QualifiedIdentifier -> QualifiedIdentifier -> Bool # (/=) :: QualifiedIdentifier -> QualifiedIdentifier -> Bool # | |
| Ord QualifiedIdentifier Source # | |
Defined in PostgREST.Types Methods compare :: QualifiedIdentifier -> QualifiedIdentifier -> Ordering # (<) :: QualifiedIdentifier -> QualifiedIdentifier -> Bool # (<=) :: QualifiedIdentifier -> QualifiedIdentifier -> Bool # (>) :: QualifiedIdentifier -> QualifiedIdentifier -> Bool # (>=) :: QualifiedIdentifier -> QualifiedIdentifier -> Bool # max :: QualifiedIdentifier -> QualifiedIdentifier -> QualifiedIdentifier # min :: QualifiedIdentifier -> QualifiedIdentifier -> QualifiedIdentifier # | |
| Show QualifiedIdentifier Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> QualifiedIdentifier -> ShowS # show :: QualifiedIdentifier -> String # showList :: [QualifiedIdentifier] -> ShowS # | |
data RelationType Source #
Instances
| Eq RelationType Source # | |
Defined in PostgREST.Types | |
| Show RelationType Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> RelationType -> ShowS # show :: RelationType -> String # showList :: [RelationType] -> ShowS # | |
The name Relation here is used with the meaning
"What is the relation between the current node and the parent node".
It has nothing to do with PostgreSQL referring to tables/views as relations.
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
| |
isSelfJoin :: Relation -> Bool Source #
data PayloadJSON Source #
Constructors
| ProcessedJSON | Cached attributes of a JSON payload |
Fields
| |
| RawJSON | |
Fields
| |
Instances
| Eq PayloadJSON Source # | |
Defined in PostgREST.Types | |
| Show PayloadJSON Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> PayloadJSON -> ShowS # show :: PayloadJSON -> String # showList :: [PayloadJSON] -> ShowS # | |
Constructors
| Proxy | |
data LogicOperator Source #
Instances
| Eq LogicOperator Source # | |
Defined in PostgREST.Types Methods (==) :: LogicOperator -> LogicOperator -> Bool # (/=) :: LogicOperator -> LogicOperator -> Bool # | |
| Show LogicOperator Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> LogicOperator -> ShowS # show :: LogicOperator -> String # showList :: [LogicOperator] -> ShowS # | |
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
type JsonPath = [JsonOperation] Source #
Json path operations as specified in https://www.postgresql.org/docs/9.4/static/functions-json.html
data JsonOperation Source #
Represents the single arrow `->` or double arrow ->> operators
Constructors
| JArrow | |
Fields
| |
| J2Arrow | |
Fields
| |
Instances
| Eq JsonOperation Source # | |
Defined in PostgREST.Types Methods (==) :: JsonOperation -> JsonOperation -> Bool # (/=) :: JsonOperation -> JsonOperation -> Bool # | |
| Show JsonOperation Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> JsonOperation -> ShowS # show :: JsonOperation -> String # showList :: [JsonOperation] -> ShowS # | |
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.Types | |
| Show JsonOperand Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> JsonOperand -> ShowS # show :: JsonOperand -> String # showList :: [JsonOperand] -> ShowS # | |
Custom guc header, it's obtained by parsing the json in a: `SET LOCAL "response.headers" = '[{"Set-Cookie": ".."}]'
type RelationDetail = Text 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 SelectItem = (Field, Maybe Cast, Maybe Alias, Maybe RelationDetail) Source #
type EmbedPath = [Text] Source #
Path of the embedded levels, e.g "clients.projects.name=eq.." gives Path ["clients", "projects"]
data JoinCondition Source #
Constructors
| JoinCondition (QualifiedIdentifier, FieldName) (QualifiedIdentifier, FieldName) |
Instances
| Eq JoinCondition Source # | |
Defined in PostgREST.Types Methods (==) :: JoinCondition -> JoinCondition -> Bool # (/=) :: JoinCondition -> JoinCondition -> Bool # | |
| Show JoinCondition Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> JoinCondition -> ShowS # show :: JoinCondition -> String # showList :: [JoinCondition] -> ShowS # | |
Constructors
| Select | |
Fields
| |
data MutateQuery Source #
Instances
| Eq MutateQuery Source # | |
Defined in PostgREST.Types | |
| Show MutateQuery Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> MutateQuery -> ShowS # show :: MutateQuery -> String # showList :: [MutateQuery] -> ShowS # | |
Constructors
| DbRead ReadRequest | |
| DbMutate MutateRequest |
type ReadRequest = Tree ReadNode Source #
type ReadNode = (ReadQuery, (NodeName, Maybe Relation, Maybe Alias, Maybe RelationDetail, Depth)) Source #
type MutateRequest = MutateQuery Source #
Instances
| Eq PgVersion Source # | |
| Ord PgVersion Source # | |
| Show PgVersion Source # | |
minimumPgVersion :: PgVersion Source #
Tells the minimum PostgreSQL version required by this version of PostgREST
jspath expression, e.g. .property, .property[0] or ."property-dash"
data ConnectionStatus Source #
Current database connection status data ConnectionStatus
Constructors
| NotConnected | |
| Connected PgVersion | |
| FatalConnectionError Text |
Instances
| Eq ConnectionStatus Source # | |
Defined in PostgREST.Types Methods (==) :: ConnectionStatus -> ConnectionStatus -> Bool # (/=) :: ConnectionStatus -> ConnectionStatus -> Bool # | |
| Show ConnectionStatus Source # | |
Defined in PostgREST.Types Methods showsPrec :: Int -> ConnectionStatus -> ShowS # show :: ConnectionStatus -> String # showList :: [ConnectionStatus] -> ShowS # | |