diff --git a/postgrest.cabal b/postgrest.cabal
index d2563c9ad07..2d2f3a7b87f 100644
--- a/postgrest.cabal
+++ b/postgrest.cabal
@@ -204,11 +204,11 @@ test-suite spec
Feature.OptionsSpec
Feature.Query.AndOrParamsSpec
Feature.Query.ComputedRelsSpec
+ Feature.Query.CustomMediaSpec
Feature.Query.DeleteSpec
Feature.Query.EmbedDisambiguationSpec
Feature.Query.EmbedInnerJoinSpec
Feature.Query.ErrorSpec
- Feature.Query.HtmlRawOutputSpec
Feature.Query.InsertSpec
Feature.Query.JsonOperatorSpec
Feature.Query.MultipleSchemaSpec
diff --git a/src/PostgREST/App.hs b/src/PostgREST/App.hs
index c8239db0ce1..aa175ff6983 100644
--- a/src/PostgREST/App.hs
+++ b/src/PostgREST/App.hs
@@ -220,7 +220,7 @@ handleRequest AuthResult{..} conf appState authenticated prepared pgVer apiReq@A
return $ pgrstResponse metrics pgrst
(ActionInspect headersOnly, TargetDefaultSpec tSchema) -> do
- (planTime', iPlan) <- withTiming $ liftEither $ Plan.inspectPlan conf apiReq
+ (planTime', iPlan) <- withTiming $ liftEither $ Plan.inspectPlan apiReq
(rsTime', oaiResult) <- withTiming $ runQuery roleIsoLvl (Plan.ipTxmode iPlan) $ Query.openApiQuery sCache pgVer conf tSchema
(renderTime', pgrst) <- withTiming $ liftEither $ Response.openApiResponse (T.decodeUtf8 prettyVersion, docsVersion) headersOnly oaiResult conf sCache iSchema iNegotiatedByProfile
let metrics = Map.fromList [(SMPlan, planTime'), (SMQuery, rsTime'), (SMRender, renderTime'), jwtTime]
diff --git a/src/PostgREST/Error.hs b/src/PostgREST/Error.hs
index 9d4ef08370e..b05e7744a63 100644
--- a/src/PostgREST/Error.hs
+++ b/src/PostgREST/Error.hs
@@ -91,7 +91,7 @@ instance PgrstError ApiRequestError where
status SingularityError{} = HTTP.status406
status PGRSTParseError = HTTP.status500
- headers SingularityError{} = [MediaType.toContentType $ MTSingularJSON False]
+ headers SingularityError{} = [MediaType.toContentType $ MTVndSingularJSON False]
headers _ = mempty
toJsonPgrstError :: ErrorCode -> Text -> Maybe JSON.Value -> Maybe JSON.Value -> JSON.Value
diff --git a/src/PostgREST/MediaType.hs b/src/PostgREST/MediaType.hs
index 0d49ba9ca27..9a54286b8af 100644
--- a/src/PostgREST/MediaType.hs
+++ b/src/PostgREST/MediaType.hs
@@ -1,9 +1,10 @@
+{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
module PostgREST.MediaType
( MediaType(..)
- , MTPlanOption (..)
- , MTPlanFormat (..)
+ , MTVndPlanOption (..)
+ , MTVndPlanFormat (..)
, toContentType
, toMime
, decodeMediaType
@@ -19,8 +20,6 @@ import Protolude
-- | Enumeration of currently supported media types
data MediaType
= MTApplicationJSON
- | MTArrayJSONStrip
- | MTSingularJSON Bool
| MTGeoJSON
| MTTextCSV
| MTTextPlain
@@ -30,32 +29,23 @@ data MediaType
| MTOctetStream
| MTAny
| MTOther ByteString
- -- TODO MTPlan should only have its options as [Text]. Its ResultAggregate should have the typed attributes.
- | MTPlan MediaType MTPlanFormat [MTPlanOption]
- deriving Show
-instance Eq MediaType where
- MTApplicationJSON == MTApplicationJSON = True
- MTArrayJSONStrip == MTArrayJSONStrip = True
- MTSingularJSON x == MTSingularJSON y = x == y
- MTGeoJSON == MTGeoJSON = True
- MTTextCSV == MTTextCSV = True
- MTTextPlain == MTTextPlain = True
- MTTextXML == MTTextXML = True
- MTOpenAPI == MTOpenAPI = True
- MTUrlEncoded == MTUrlEncoded = True
- MTOctetStream == MTOctetStream = True
- MTAny == MTAny = True
- MTOther x == MTOther y = x == y
- MTPlan{} == MTPlan{} = True
- _ == _ = False
+ -- vendored media types
+ | MTVndArrayJSONStrip
+ | MTVndSingularJSON Bool
+ -- TODO MTVndPlan should only have its options as [Text]. Its ResultAggregate should have the typed attributes.
+ | MTVndPlan MediaType MTVndPlanFormat [MTVndPlanOption]
+ deriving (Eq, Show, Generic)
+instance Hashable MediaType
-data MTPlanOption
+data MTVndPlanOption
= PlanAnalyze | PlanVerbose | PlanSettings | PlanBuffers | PlanWAL
- deriving (Eq, Show)
+ deriving (Eq, Show, Generic)
+instance Hashable MTVndPlanOption
-data MTPlanFormat
+data MTVndPlanFormat
= PlanJSON | PlanText
- deriving (Eq, Show)
+ deriving (Eq, Show, Generic)
+instance Hashable MTVndPlanFormat
-- | Convert MediaType to a Content-Type HTTP Header
toContentType :: MediaType -> Header
@@ -69,31 +59,31 @@ toContentType ct = (hContentType, toMime ct <> charset)
-- | Convert from MediaType to a ByteString representing the mime type
toMime :: MediaType -> ByteString
toMime MTApplicationJSON = "application/json"
-toMime MTArrayJSONStrip = "application/vnd.pgrst.array+json;nulls=stripped"
+toMime MTVndArrayJSONStrip = "application/vnd.pgrst.array+json;nulls=stripped"
toMime MTGeoJSON = "application/geo+json"
toMime MTTextCSV = "text/csv"
toMime MTTextPlain = "text/plain"
toMime MTTextXML = "text/xml"
toMime MTOpenAPI = "application/openapi+json"
-toMime (MTSingularJSON True) = "application/vnd.pgrst.object+json;nulls=stripped"
-toMime (MTSingularJSON False) = "application/vnd.pgrst.object+json"
+toMime (MTVndSingularJSON True) = "application/vnd.pgrst.object+json;nulls=stripped"
+toMime (MTVndSingularJSON False) = "application/vnd.pgrst.object+json"
toMime MTUrlEncoded = "application/x-www-form-urlencoded"
toMime MTOctetStream = "application/octet-stream"
toMime MTAny = "*/*"
toMime (MTOther ct) = ct
-toMime (MTPlan mt fmt opts) =
+toMime (MTVndPlan mt fmt opts) =
"application/vnd.pgrst.plan+" <> toMimePlanFormat fmt <>
("; for=\"" <> toMime mt <> "\"") <>
(if null opts then mempty else "; options=" <> BS.intercalate "|" (toMimePlanOption <$> opts))
-toMimePlanOption :: MTPlanOption -> ByteString
+toMimePlanOption :: MTVndPlanOption -> ByteString
toMimePlanOption PlanAnalyze = "analyze"
toMimePlanOption PlanVerbose = "verbose"
toMimePlanOption PlanSettings = "settings"
toMimePlanOption PlanBuffers = "buffers"
toMimePlanOption PlanWAL = "wal"
-toMimePlanFormat :: MTPlanFormat -> ByteString
+toMimePlanFormat :: MTVndPlanFormat -> ByteString
toMimePlanFormat PlanJSON = "json"
toMimePlanFormat PlanText = "text"
@@ -103,25 +93,25 @@ toMimePlanFormat PlanText = "text"
-- MTApplicationJSON
--
-- >>> decodeMediaType "application/vnd.pgrst.plan;"
--- MTPlan MTApplicationJSON PlanText []
+-- MTVndPlan MTApplicationJSON PlanText []
--
-- >>> decodeMediaType "application/vnd.pgrst.plan;for=\"application/json\""
--- MTPlan MTApplicationJSON PlanText []
+-- MTVndPlan MTApplicationJSON PlanText []
--
-- >>> decodeMediaType "application/vnd.pgrst.plan+json;for=\"text/csv\""
--- MTPlan MTTextCSV PlanJSON []
+-- MTVndPlan MTTextCSV PlanJSON []
--
-- >>> decodeMediaType "application/vnd.pgrst.array+json;nulls=stripped"
--- MTArrayJSONStrip
+-- MTVndArrayJSONStrip
--
-- >>> decodeMediaType "application/vnd.pgrst.array+json"
-- MTApplicationJSON
--
-- >>> decodeMediaType "application/vnd.pgrst.object+json;nulls=stripped"
--- MTSingularJSON True
+-- MTVndSingularJSON True
--
-- >>> decodeMediaType "application/vnd.pgrst.object+json"
--- MTSingularJSON False
+-- MTVndSingularJSON False
decodeMediaType :: BS.ByteString -> MediaType
decodeMediaType mt =
@@ -145,11 +135,11 @@ decodeMediaType mt =
other:_ -> MTOther other
_ -> MTAny
where
- checkArrayNullStrip ["nulls=stripped"] = MTArrayJSONStrip
+ checkArrayNullStrip ["nulls=stripped"] = MTVndArrayJSONStrip
checkArrayNullStrip _ = MTApplicationJSON
- checkSingularNullStrip ["nulls=stripped"] = MTSingularJSON True
- checkSingularNullStrip _ = MTSingularJSON False
+ checkSingularNullStrip ["nulls=stripped"] = MTVndSingularJSON True
+ checkSingularNullStrip _ = MTVndSingularJSON False
getPlan fmt rest =
let
@@ -161,7 +151,7 @@ decodeMediaType mt =
strippedFor <- BS.stripPrefix "for=" foundFor
pure . decodeMediaType $ dropAround (== BS.c2w '"') strippedFor
in
- MTPlan mtFor fmt $
+ MTVndPlan mtFor fmt $
[PlanAnalyze | inOpts "analyze" ] ++
[PlanVerbose | inOpts "verbose" ] ++
[PlanSettings | inOpts "settings"] ++
diff --git a/src/PostgREST/Plan.hs b/src/PostgREST/Plan.hs
index 8ce2873ce42..4948b695253 100644
--- a/src/PostgREST/Plan.hs
+++ b/src/PostgREST/Plan.hs
@@ -44,8 +44,7 @@ import PostgREST.ApiRequest (Action (..),
Payload (..))
import PostgREST.Config (AppConfig (..))
import PostgREST.Error (Error (..))
-import PostgREST.MediaType (MTPlanFormat (..),
- MediaType (..))
+import PostgREST.MediaType (MediaType (..))
import PostgREST.Query.SqlFragment (sourceCTEName)
import PostgREST.RangeQuery (NonnegRange, allRange,
convertToLimitZeroRange,
@@ -53,6 +52,7 @@ import PostgREST.RangeQuery (NonnegRange, allRange,
import PostgREST.SchemaCache (SchemaCache (..))
import PostgREST.SchemaCache.Identifiers (FieldName,
QualifiedIdentifier (..),
+ RelIdentifier (..),
Schema)
import PostgREST.SchemaCache.Relationship (Cardinality (..),
Junction (..),
@@ -61,7 +61,7 @@ import PostgREST.SchemaCache.Relationship (Cardinality (..),
relIsToOne)
import PostgREST.SchemaCache.Representations (DataRepresentation (..),
RepresentationsMap)
-import PostgREST.SchemaCache.Routine (ResultAggregate (..),
+import PostgREST.SchemaCache.Routine (MediaHandler (..),
Routine (..),
RoutineMap,
RoutineParam (..),
@@ -93,16 +93,18 @@ import Protolude hiding (from)
data WrappedReadPlan = WrappedReadPlan {
wrReadPlan :: ReadPlanTree
, wrTxMode :: SQL.Mode
-, wrResAgg :: ResultAggregate
+, wrHandler :: MediaHandler
, wrMedia :: MediaType
+, wrIdent :: QualifiedIdentifier
}
data MutateReadPlan = MutateReadPlan {
mrReadPlan :: ReadPlanTree
, mrMutatePlan :: MutatePlan
, mrTxMode :: SQL.Mode
-, mrResAgg :: ResultAggregate
+, mrHandler :: MediaHandler
, mrMedia :: MediaType
+, mrIdent :: QualifiedIdentifier
}
data CallReadPlan = CallReadPlan {
@@ -110,8 +112,9 @@ data CallReadPlan = CallReadPlan {
, crCallPlan :: CallPlan
, crTxMode :: SQL.Mode
, crProc :: Routine
-, crResAgg :: ResultAggregate
+, crHandler :: MediaHandler
, crMedia :: MediaType
+, crIdent :: QualifiedIdentifier
}
data InspectPlan = InspectPlan {
@@ -122,17 +125,17 @@ data InspectPlan = InspectPlan {
wrappedReadPlan :: QualifiedIdentifier -> AppConfig -> SchemaCache -> ApiRequest -> Either Error WrappedReadPlan
wrappedReadPlan identifier conf sCache apiRequest@ApiRequest{iPreferences=Preferences{..},..} = do
rPlan <- readPlan identifier conf sCache apiRequest
- mediaType <- mapLeft ApiRequestError $ negotiateContent conf iAction iAcceptMediaType
+ (hdler, mediaType) <- mapLeft ApiRequestError $ negotiateContent conf apiRequest identifier iAcceptMediaType (dbMediaHandlers sCache)
if not (null invalidPrefs) && preferHandling == Just Strict then Left $ ApiRequestError $ InvalidPreferences invalidPrefs else Right ()
- return $ WrappedReadPlan rPlan SQL.Read (mediaToAggregate mediaType apiRequest) mediaType
+ return $ WrappedReadPlan rPlan SQL.Read hdler mediaType identifier
mutateReadPlan :: Mutation -> ApiRequest -> QualifiedIdentifier -> AppConfig -> SchemaCache -> Either Error MutateReadPlan
mutateReadPlan mutation apiRequest@ApiRequest{iPreferences=Preferences{..},..} identifier conf sCache = do
rPlan <- readPlan identifier conf sCache apiRequest
mPlan <- mutatePlan mutation identifier apiRequest sCache rPlan
- mediaType <- mapLeft ApiRequestError $ negotiateContent conf iAction iAcceptMediaType
if not (null invalidPrefs) && preferHandling == Just Strict then Left $ ApiRequestError $ InvalidPreferences invalidPrefs else Right ()
- return $ MutateReadPlan rPlan mPlan SQL.Write (mediaToAggregate mediaType apiRequest) mediaType
+ (hdler, mediaType) <- mapLeft ApiRequestError $ negotiateContent conf apiRequest identifier iAcceptMediaType (dbMediaHandlers sCache)
+ return $ MutateReadPlan rPlan mPlan SQL.Write hdler mediaType identifier
callReadPlan :: QualifiedIdentifier -> AppConfig -> SchemaCache -> ApiRequest -> InvokeMethod -> Either Error CallReadPlan
callReadPlan identifier conf sCache apiRequest@ApiRequest{iPreferences=Preferences{..},..} invMethod = do
@@ -156,15 +159,19 @@ callReadPlan identifier conf sCache apiRequest@ApiRequest{iPreferences=Preferenc
(InvPost, Routine.Immutable) -> SQL.Read
(InvPost, Routine.Volatile) -> SQL.Write
cPlan = callPlan proc apiRequest paramKeys args rPlan
- mediaType <- mapLeft ApiRequestError $ negotiateContent conf iAction iAcceptMediaType
+ (hdler, mediaType) <- mapLeft ApiRequestError $ negotiateContent conf apiRequest relIdentifier iAcceptMediaType (dbMediaHandlers sCache)
if not (null invalidPrefs) && preferHandling == Just Strict then Left $ ApiRequestError $ InvalidPreferences invalidPrefs else Right ()
- return $ CallReadPlan rPlan cPlan txMode proc (mediaToAggregate mediaType apiRequest) mediaType
+ return $ CallReadPlan rPlan cPlan txMode proc hdler mediaType relIdentifier
where
qsParams' = QueryParams.qsParams iQueryParams
-inspectPlan :: AppConfig -> ApiRequest -> Either Error InspectPlan
-inspectPlan conf apiRequest = do
- mediaType <- mapLeft ApiRequestError $ negotiateContent conf (iAction apiRequest) (iAcceptMediaType apiRequest)
+inspectPlan :: ApiRequest -> Either Error InspectPlan
+inspectPlan apiRequest = do
+ let producedMTs = [MTOpenAPI, MTApplicationJSON, MTAny]
+ accepts = iAcceptMediaType apiRequest
+ mediaType <- if not . null $ L.intersect accepts producedMTs
+ then Right MTOpenAPI
+ else Left . ApiRequestError . MediaTypeError $ MediaType.toMime <$> accepts
return $ InspectPlan mediaType SQL.Read
{-|
@@ -824,52 +831,34 @@ inferColsEmbedNeeds (Node ReadPlan{select} forest) pkCols
addFilterToLogicForest :: CoercibleFilter -> [CoercibleLogicTree] -> [CoercibleLogicTree]
addFilterToLogicForest flt lf = CoercibleStmnt flt : lf
-mediaToAggregate :: MediaType -> ApiRequest -> ResultAggregate
-mediaToAggregate mt apiReq@ApiRequest{iAction=act, iPreferences=Preferences{preferRepresentation=rep}} =
- if noAgg then NoAgg
- else case mt of
- MTApplicationJSON -> BuiltinAggJson
- MTSingularJSON strip -> BuiltinAggSingleJson strip
- MTArrayJSONStrip -> BuiltinAggArrayJsonStrip
- MTGeoJSON -> BuiltinAggGeoJson
- MTTextCSV -> BuiltinAggCsv
- MTAny -> BuiltinAggJson
- MTOpenAPI -> BuiltinAggJson
- MTUrlEncoded -> NoAgg -- TODO: unreachable since a previous step (producedMediaTypes) whitelists the media types that can become aggregates.
-
- -- Doing `Accept: application/vnd.pgrst.plan; for="application/vnd.pgrst.plan"` doesn't make sense, so we just empty the body.
- -- TODO: fail instead to be more strict
- MTPlan (MTPlan{}) _ _ -> NoAgg
- MTPlan media _ _ -> mediaToAggregate media apiReq
- _ -> NoAgg
- where
- noAgg = case act of
- ActionMutate _ -> rep == Just HeadersOnly || rep == Just None || isNothing rep
- ActionRead _isHead -> _isHead -- no need for an aggregate on HEAD https://github.com/PostgREST/postgrest/issues/2849
- ActionInvoke invMethod -> invMethod == InvHead
- _ -> False
-
-- | Do content negotiation. i.e. choose a media type based on the intersection of accepted/produced media types.
-negotiateContent :: AppConfig -> Action -> [MediaType] -> Either ApiRequestError MediaType
-negotiateContent conf action accepts =
- case firstAcceptedPick of
- Just MTAny -> Right MTApplicationJSON -- by default(for */*) we respond with json
- Just mt -> Right mt
- Nothing -> Left . MediaTypeError $ map MediaType.toMime accepts
+negotiateContent :: AppConfig -> ApiRequest -> QualifiedIdentifier -> [MediaType] ->
+ HM.HashMap (RelIdentifier, MediaType) MediaHandler -> Either ApiRequestError (MediaHandler, MediaType)
+negotiateContent conf ApiRequest{iAction=act, iPreferences=Preferences{preferRepresentation=rep}} identifier accepts produces =
+ mtAnyToJSON $ case (act, firstAcceptedPick) of
+ (_, Nothing) -> Left . MediaTypeError $ map MediaType.toMime accepts
+ (ActionMutate _, Just (x, mt)) -> Right (if rep == Just Full then x else NoAgg, mt)
+ -- no need for an aggregate on HEAD https://github.com/PostgREST/postgrest/issues/2849
+ -- TODO: despite no aggregate, these are responding with a Content-Type, which is not correct.
+ (ActionRead True, Just (_, mt)) -> Right (NoAgg, mt)
+ (ActionInvoke InvHead, Just (_, mt)) -> Right (NoAgg, mt)
+ (_, Just (x, mt)) -> Right (x, mt)
where
+ -- TODO initial */* is not overridable
+ -- initial handlers in the schema cache have a */* to BuiltinAggJson but they don't preserve the media type (application/json)
+ -- for now we just convert the resultant */* to application/json here
+ mtAnyToJSON = mapRight (\(x, y) -> (x, if y == MTAny then MTApplicationJSON else y))
-- if there are multiple accepted media types, pick the first
- firstAcceptedPick = listToMaybe $ L.intersect accepts $ producedMediaTypes conf action
-
-producedMediaTypes :: AppConfig -> Action -> [MediaType]
-producedMediaTypes conf action =
- case action of
- ActionRead _ -> defaultMediaTypes
- ActionInvoke _ -> defaultMediaTypes
- ActionInfo -> defaultMediaTypes
- ActionMutate _ -> defaultMediaTypes
- ActionInspect _ -> inspectMediaTypes
- where
- inspectMediaTypes = [MTOpenAPI, MTApplicationJSON, MTArrayJSONStrip, MTAny]
- defaultMediaTypes =
- [MTApplicationJSON, MTArrayJSONStrip, MTSingularJSON True, MTSingularJSON False, MTGeoJSON, MTTextCSV] ++
- [MTPlan MTApplicationJSON PlanText mempty | configDbPlanEnabled conf] ++ [MTAny]
+ firstAcceptedPick = listToMaybe $ mapMaybe searchMT accepts
+ lookupIdent mt = -- first search for an aggregate that applies to the particular relation, then for one that applies to anyelement
+ HM.lookup (RelId identifier, mt) produces <|> HM.lookup (RelAnyElement, mt) produces
+ searchMT mt = case mt of
+ -- all the vendored media types have special handling as they have media type parameters, they cannot be overridden
+ m@(MTVndSingularJSON strip) -> Just (BuiltinAggSingleJson strip, m)
+ m@MTVndArrayJSONStrip -> Just (BuiltinAggArrayJsonStrip, m)
+ m@(MTVndPlan (MTVndSingularJSON strip) _ _) -> mtPlanToNothing $ Just (BuiltinAggSingleJson strip, m)
+ m@(MTVndPlan MTVndArrayJSONStrip _ _) -> mtPlanToNothing $ Just (BuiltinAggArrayJsonStrip, m)
+ -- all the other media types can be overridden
+ m@(MTVndPlan mType _ _) -> mtPlanToNothing $ (,) <$> lookupIdent mType <*> pure m
+ x -> (,) <$> lookupIdent x <*> pure x
+ mtPlanToNothing x = if configDbPlanEnabled conf then x else Nothing -- don't find anything if the plan media type is not allowed
diff --git a/src/PostgREST/Query.hs b/src/PostgREST/Query.hs
index 49fae72bf07..85e08dfe6c6 100644
--- a/src/PostgREST/Query.hs
+++ b/src/PostgREST/Query.hs
@@ -71,6 +71,7 @@ readQuery WrappedReadPlan{..} conf@AppConfig{..} apiReq@ApiRequest{iPreferences=
resultSet <-
lift . SQL.statement mempty $
Statements.prepareRead
+ wrIdent
(QueryBuilder.readPlanToQuery wrReadPlan)
(if preferCount == Just EstimatedCount then
-- LIMIT maxRows + 1 so we can determine below that maxRows was surpassed
@@ -80,7 +81,7 @@ readQuery WrappedReadPlan{..} conf@AppConfig{..} apiReq@ApiRequest{iPreferences=
)
(shouldCount preferCount)
wrMedia
- wrResAgg
+ wrHandler
configDbPreparedStatements
failNotSingular wrMedia resultSet
optionalRollback conf apiReq
@@ -155,13 +156,14 @@ invokeQuery rout CallReadPlan{..} apiReq@ApiRequest{iPreferences=Preferences{..}
resultSet <-
lift . SQL.statement mempty $
Statements.prepareCall
+ crIdent
rout
(QueryBuilder.callPlanToQuery crCallPlan pgVer)
(QueryBuilder.readPlanToQuery crReadPlan)
(QueryBuilder.readPlanToCountQuery crReadPlan)
(shouldCount preferCount)
crMedia
- crResAgg
+ crHandler
configDbPreparedStatements
optionalRollback conf apiReq
@@ -186,17 +188,18 @@ openApiQuery sCache pgVer AppConfig{..} tSchema =
pure Nothing
writeQuery :: MutateReadPlan -> ApiRequest -> AppConfig -> DbHandler ResultSet
-writeQuery MutateReadPlan{mrReadPlan, mrMutatePlan, mrResAgg, mrMedia} ApiRequest{iPreferences=Preferences{..}} conf =
+writeQuery MutateReadPlan{..} ApiRequest{iPreferences=Preferences{..}} conf =
let
(isInsert, pkCols) = case mrMutatePlan of {Insert{insPkCols} -> (True, insPkCols); _ -> (False, mempty);}
in
lift . SQL.statement mempty $
Statements.prepareWrite
+ mrIdent
(QueryBuilder.readPlanToQuery mrReadPlan)
(QueryBuilder.mutatePlanToQuery mrMutatePlan)
isInsert
mrMedia
- mrResAgg
+ mrHandler
preferRepresentation
pkCols
(configDbPreparedStatements conf)
@@ -207,7 +210,7 @@ writeQuery MutateReadPlan{mrReadPlan, mrMutatePlan, mrResAgg, mrMedia} ApiReques
failNotSingular :: MediaType -> ResultSet -> DbHandler ()
failNotSingular _ RSPlan{} = pure ()
failNotSingular mediaType RSStandard{rsQueryTotal=queryTotal} =
- when (elem mediaType [MTSingularJSON True,MTSingularJSON False] && queryTotal /= 1) $ do
+ when (elem mediaType [MTVndSingularJSON True, MTVndSingularJSON False] && queryTotal /= 1) $ do
lift SQL.condemn
throwError $ Error.ApiRequestError . ApiRequestTypes.SingularityError $ toInteger queryTotal
diff --git a/src/PostgREST/Query/SqlFragment.hs b/src/PostgREST/Query/SqlFragment.hs
index c3dfaf55d20..af64e670cda 100644
--- a/src/PostgREST/Query/SqlFragment.hs
+++ b/src/PostgREST/Query/SqlFragment.hs
@@ -7,7 +7,7 @@ Description : Helper functions for PostgREST.QueryBuilder.
-}
module PostgREST.Query.SqlFragment
( noLocationF
- , aggF
+ , handlerF
, countF
, fromQi
, limitOffsetF
@@ -65,8 +65,8 @@ import PostgREST.ApiRequest.Types (Alias, Cast,
QuantOperator (..),
SimpleOperator (..),
TrileanVal (..))
-import PostgREST.MediaType (MTPlanFormat (..),
- MTPlanOption (..))
+import PostgREST.MediaType (MTVndPlanFormat (..),
+ MTVndPlanOption (..))
import PostgREST.Plan.ReadPlan (JoinCondition (..))
import PostgREST.Plan.Types (CoercibleField (..),
CoercibleFilter (..),
@@ -77,7 +77,7 @@ import PostgREST.RangeQuery (NonnegRange, allRange,
rangeLimit, rangeOffset)
import PostgREST.SchemaCache.Identifiers (FieldName,
QualifiedIdentifier (..))
-import PostgREST.SchemaCache.Routine (ResultAggregate (..),
+import PostgREST.SchemaCache.Routine (MediaHandler (..),
Routine (..),
funcReturnsScalar,
funcReturnsSetOfScalar,
@@ -212,6 +212,11 @@ asJsonF rout strip
asGeoJsonF :: SQL.Snippet
asGeoJsonF = "json_build_object('type', 'FeatureCollection', 'features', coalesce(json_agg(ST_AsGeoJSON(_postgrest_t)::json), '[]'))"
+customFuncF :: Maybe Routine -> QualifiedIdentifier -> QualifiedIdentifier -> SQL.Snippet
+customFuncF rout funcQi target
+ | (funcReturnsScalar <$> rout) == Just True = fromQi funcQi <> "(_postgrest_t.pgrst_scalar)"
+ | otherwise = fromQi funcQi <> "(_postgrest_t::" <> fromQi target <> ")"
+
locationF :: [Text] -> SQL.Snippet
locationF pKeys = [qc|(
WITH data AS (SELECT row_to_json(_) AS row FROM {sourceCTEName} AS _ LIMIT 1)
@@ -455,13 +460,13 @@ intercalateSnippet :: ByteString -> [SQL.Snippet] -> SQL.Snippet
intercalateSnippet _ [] = mempty
intercalateSnippet frag snippets = foldr1 (\a b -> a <> SQL.sql frag <> b) snippets
-explainF :: MTPlanFormat -> [MTPlanOption] -> SQL.Snippet -> SQL.Snippet
+explainF :: MTVndPlanFormat -> [MTVndPlanOption] -> SQL.Snippet -> SQL.Snippet
explainF fmt opts snip =
"EXPLAIN (" <>
SQL.sql (BS.intercalate ", " (fmtPlanFmt fmt : (fmtPlanOpt <$> opts))) <>
") " <> snip
where
- fmtPlanOpt :: MTPlanOption -> BS.ByteString
+ fmtPlanOpt :: MTVndPlanOption -> BS.ByteString
fmtPlanOpt PlanAnalyze = "ANALYZE"
fmtPlanOpt PlanVerbose = "VERBOSE"
fmtPlanOpt PlanSettings = "SETTINGS"
@@ -486,11 +491,12 @@ setConfigLocalJson prefix keyVals = [setConfigLocal mempty (prefix, gucJsonVal k
arrayByteStringToText :: [(ByteString, ByteString)] -> [(Text,Text)]
arrayByteStringToText keyVal = (T.decodeUtf8 *** T.decodeUtf8) <$> keyVal
-aggF :: Maybe Routine -> ResultAggregate -> SQL.Snippet
-aggF rout = \case
- BuiltinAggJson -> asJsonF rout False
+handlerF :: Maybe Routine -> QualifiedIdentifier -> MediaHandler -> SQL.Snippet
+handlerF rout target = \case
BuiltinAggArrayJsonStrip -> asJsonF rout True
BuiltinAggSingleJson strip -> asJsonSingleF rout strip
- BuiltinAggGeoJson -> asGeoJsonF
- BuiltinAggCsv -> asCsvF
+ BuiltinOvAggJson -> asJsonF rout False
+ BuiltinOvAggGeoJson -> asGeoJsonF
+ BuiltinOvAggCsv -> asCsvF
+ CustomFunc funcQi -> customFuncF rout funcQi target
NoAgg -> "''::text"
diff --git a/src/PostgREST/Query/Statements.hs b/src/PostgREST/Query/Statements.hs
index b9d9c8f5bd4..a6733eccc4b 100644
--- a/src/PostgREST/Query/Statements.hs
+++ b/src/PostgREST/Query/Statements.hs
@@ -25,11 +25,12 @@ import qualified Hasql.Statement as SQL
import Control.Lens ((^?))
import PostgREST.ApiRequest.Preferences
-import PostgREST.MediaType (MTPlanFormat (..),
- MediaType (..))
+import PostgREST.MediaType (MTVndPlanFormat (..),
+ MediaType (..))
import PostgREST.Query.SqlFragment
-import PostgREST.SchemaCache.Routine (ResultAggregate (..),
- Routine, funcReturnsSingle)
+import PostgREST.SchemaCache.Identifiers (QualifiedIdentifier)
+import PostgREST.SchemaCache.Routine (MediaHandler (..), Routine,
+ funcReturnsSingle)
import Protolude
@@ -53,9 +54,9 @@ data ResultSet
| RSPlan BS.ByteString -- ^ the plan of the query
-prepareWrite :: SQL.Snippet -> SQL.Snippet -> Bool -> MediaType -> ResultAggregate ->
+prepareWrite :: QualifiedIdentifier -> SQL.Snippet -> SQL.Snippet -> Bool -> MediaType -> MediaHandler ->
Maybe PreferRepresentation -> [Text] -> Bool -> SQL.Statement () ResultSet
-prepareWrite selectQuery mutateQuery isInsert mt rAgg rep pKeys =
+prepareWrite qi selectQuery mutateQuery isInsert mt handler rep pKeys =
SQL.dynamicallyParameterized (mtSnippet mt snippet) decodeIt
where
snippet =
@@ -64,7 +65,7 @@ prepareWrite selectQuery mutateQuery isInsert mt rAgg rep pKeys =
"'' AS total_result_set, " <>
"pg_catalog.count(_postgrest_t) AS page_total, " <>
locF <> " AS header, " <>
- aggF Nothing rAgg <> " AS body, " <>
+ handlerF Nothing qi handler <> " AS body, " <>
responseHeadersF <> " AS response_headers, " <>
responseStatusF <> " AS response_status " <>
"FROM (" <> selectF <> ") _postgrest_t"
@@ -80,16 +81,16 @@ prepareWrite selectQuery mutateQuery isInsert mt rAgg rep pKeys =
selectF
-- prevent using any of the column names in ?select= when no response is returned from the CTE
- | rAgg == NoAgg = "SELECT * FROM " <> sourceCTE
- | otherwise = selectQuery
+ | handler == NoAgg = "SELECT * FROM " <> sourceCTE
+ | otherwise = selectQuery
decodeIt :: HD.Result ResultSet
decodeIt = case mt of
- MTPlan{} -> planRow
+ MTVndPlan{} -> planRow
_ -> fromMaybe (RSStandard Nothing 0 mempty mempty Nothing Nothing) <$> HD.rowMaybe (standardRow False)
-prepareRead :: SQL.Snippet -> SQL.Snippet -> Bool -> MediaType -> ResultAggregate -> Bool -> SQL.Statement () ResultSet
-prepareRead selectQuery countQuery countTotal mt rAgg =
+prepareRead :: QualifiedIdentifier -> SQL.Snippet -> SQL.Snippet -> Bool -> MediaType -> MediaHandler -> Bool -> SQL.Statement () ResultSet
+prepareRead qi selectQuery countQuery countTotal mt handler =
SQL.dynamicallyParameterized (mtSnippet mt snippet) decodeIt
where
snippet =
@@ -98,7 +99,7 @@ prepareRead selectQuery countQuery countTotal mt rAgg =
"SELECT " <>
countResultF <> " AS total_result_set, " <>
"pg_catalog.count(_postgrest_t) AS page_total, " <>
- aggF Nothing rAgg <> " AS body, " <>
+ handlerF Nothing qi handler <> " AS body, " <>
responseHeadersF <> " AS response_headers, " <>
responseStatusF <> " AS response_status " <>
"FROM ( SELECT * FROM " <> sourceCTE <> " ) _postgrest_t"
@@ -107,13 +108,13 @@ prepareRead selectQuery countQuery countTotal mt rAgg =
decodeIt :: HD.Result ResultSet
decodeIt = case mt of
- MTPlan{} -> planRow
- _ -> HD.singleRow $ standardRow True
+ MTVndPlan{} -> planRow
+ _ -> HD.singleRow $ standardRow True
-prepareCall :: Routine -> SQL.Snippet -> SQL.Snippet -> SQL.Snippet -> Bool ->
- MediaType -> ResultAggregate -> Bool ->
+prepareCall :: QualifiedIdentifier -> Routine -> SQL.Snippet -> SQL.Snippet -> SQL.Snippet -> Bool ->
+ MediaType -> MediaHandler -> Bool ->
SQL.Statement () ResultSet
-prepareCall rout callProcQuery selectQuery countQuery countTotal mt rAgg =
+prepareCall qi rout callProcQuery selectQuery countQuery countTotal mt handler =
SQL.dynamicallyParameterized (mtSnippet mt snippet) decodeIt
where
snippet =
@@ -124,7 +125,7 @@ prepareCall rout callProcQuery selectQuery countQuery countTotal mt rAgg =
(if funcReturnsSingle rout
then "1"
else "pg_catalog.count(_postgrest_t)") <> " AS page_total, " <>
- aggF (Just rout) rAgg <> " AS body, " <>
+ handlerF (Just rout) qi handler <> " AS body, " <>
responseHeadersF <> " AS response_headers, " <>
responseStatusF <> " AS response_status " <>
"FROM (" <> selectQuery <> ") _postgrest_t"
@@ -133,7 +134,7 @@ prepareCall rout callProcQuery selectQuery countQuery countTotal mt rAgg =
decodeIt :: HD.Result ResultSet
decodeIt = case mt of
- MTPlan{} -> planRow
+ MTVndPlan{} -> planRow
_ -> fromMaybe (RSStandard (Just 0) 0 mempty mempty Nothing Nothing) <$> HD.rowMaybe (standardRow True)
preparePlanRows :: SQL.Snippet -> Bool -> SQL.Statement () (Maybe Int64)
@@ -160,8 +161,8 @@ standardRow noLocation =
mtSnippet :: MediaType -> SQL.Snippet -> SQL.Snippet
mtSnippet mediaType snippet = case mediaType of
- MTPlan _ fmt opts -> explainF fmt opts snippet
- _ -> snippet
+ MTVndPlan _ fmt opts -> explainF fmt opts snippet
+ _ -> snippet
-- | We use rowList because when doing EXPLAIN (FORMAT TEXT), the result comes as many rows. FORMAT JSON comes as one.
planRow :: HD.Result ResultSet
diff --git a/src/PostgREST/Response/OpenAPI.hs b/src/PostgREST/Response/OpenAPI.hs
index fc137a06532..0a89334544e 100644
--- a/src/PostgREST/Response/OpenAPI.hs
+++ b/src/PostgREST/Response/OpenAPI.hs
@@ -350,7 +350,7 @@ makeProcPathItem pd = ("/rpc/" ++ toS (pdName pd), pe)
& summary .~ pSum
& description .~ mfilter (/="") pDesc
& tags .~ Set.fromList ["(rpc) " <> pdName pd]
- & produces ?~ makeMimeList [MTApplicationJSON, MTSingularJSON True, MTSingularJSON False]
+ & produces ?~ makeMimeList [MTApplicationJSON, MTVndSingularJSON True, MTVndSingularJSON False]
& at 200 ?~ "OK"
getOp = procOp
& parameters .~ makeProcGetParams (pdParams pd)
@@ -406,8 +406,8 @@ postgrestSpec (prettyVersion, docsVersion) rels pds ti (s, h, p, b) sd allowSecu
& definitions .~ fromList (makeTableDef rels <$> ti)
& parameters .~ fromList (makeParamDefs ti)
& paths .~ makePathItems pds ti
- & produces .~ makeMimeList [MTApplicationJSON, MTSingularJSON True, MTSingularJSON False, MTTextCSV]
- & consumes .~ makeMimeList [MTApplicationJSON, MTSingularJSON True, MTSingularJSON False, MTTextCSV]
+ & produces .~ makeMimeList [MTApplicationJSON, MTVndSingularJSON True, MTVndSingularJSON False, MTTextCSV]
+ & consumes .~ makeMimeList [MTApplicationJSON, MTVndSingularJSON True, MTVndSingularJSON False, MTTextCSV]
& securityDefinitions .~ makeSecurityDefinitions securityDefName allowSecurityDef
& security .~ [SecurityRequirement (fromList [(securityDefName, [])]) | allowSecurityDef]
where
diff --git a/src/PostgREST/SchemaCache.hs b/src/PostgREST/SchemaCache.hs
index 5358a05125e..a2e3e485673 100644
--- a/src/PostgREST/SchemaCache.hs
+++ b/src/PostgREST/SchemaCache.hs
@@ -28,7 +28,9 @@ module PostgREST.SchemaCache
import Control.Monad.Extra (whenJust)
+import Data.Aeson ((.=))
import qualified Data.Aeson as JSON
+import qualified Data.Aeson.Types as JSON
import qualified Data.HashMap.Strict as HM
import qualified Data.HashMap.Strict.InsOrd as HMI
import qualified Data.Set as S
@@ -48,7 +50,8 @@ import PostgREST.Config.PgVersion (PgVersion, pgVersion100,
pgVersion120)
import PostgREST.SchemaCache.Identifiers (AccessSet, FieldName,
QualifiedIdentifier (..),
- Schema)
+ RelIdentifier (..),
+ Schema, isAnyElement)
import PostgREST.SchemaCache.Relationship (Cardinality (..),
Junction (..),
Relationship (..),
@@ -56,6 +59,8 @@ import PostgREST.SchemaCache.Relationship (Cardinality (..),
import PostgREST.SchemaCache.Representations (DataRepresentation (..),
RepresentationsMap)
import PostgREST.SchemaCache.Routine (FuncVolatility (..),
+ MediaHandler (..),
+ MediaHandlerMap,
PgType (..),
RetType (..),
Routine (..),
@@ -64,6 +69,8 @@ import PostgREST.SchemaCache.Routine (FuncVolatility (..),
import PostgREST.SchemaCache.Table (Column (..), ColumnMap,
Table (..), TablesMap)
+import qualified PostgREST.MediaType as MediaType
+
import Protolude
@@ -72,8 +79,16 @@ data SchemaCache = SchemaCache
, dbRelationships :: RelationshipsMap
, dbRoutines :: RoutineMap
, dbRepresentations :: RepresentationsMap
+ , dbMediaHandlers :: MediaHandlerMap
}
- deriving (Generic, JSON.ToJSON)
+instance JSON.ToJSON SchemaCache where
+ toJSON (SchemaCache tabs rels routs reps _) = JSON.object [
+ "dbTables" .= JSON.toJSON tabs
+ , "dbRelationships" .= JSON.toJSON rels
+ , "dbRoutines" .= JSON.toJSON routs
+ , "dbRepresentations" .= JSON.toJSON reps
+ , "dbMediaHandlers" .= JSON.emptyArray
+ ]
-- | A view foreign key or primary key dependency detected on its source table
-- Each column of the key could be referenced multiple times in the view, e.g.
@@ -113,6 +128,7 @@ data KeyDep
-- | A SQL query that can be executed independently
type SqlQuery = ByteString
+
querySchemaCache :: AppConfig -> SQL.Transaction SchemaCache
querySchemaCache AppConfig{..} = do
SQL.sql "set local schema ''" -- This voids the search path. The following queries need this for getting the fully qualified name(schema.name) of every db object
@@ -123,6 +139,7 @@ querySchemaCache AppConfig{..} = do
funcs <- SQL.statement schemas $ allFunctions pgVer prepared
cRels <- SQL.statement mempty $ allComputedRels prepared
reps <- SQL.statement schemas $ dataRepresentations prepared
+ mHdlers <- SQL.statement schemas $ mediaHandlers pgVer prepared
_ <-
let sleepCall = SQL.Statement "select pg_sleep($1)" (param HE.int4) HD.noResult prepared in
whenJust configInternalSCSleep (`SQL.statement` sleepCall) -- only used for testing
@@ -135,6 +152,7 @@ querySchemaCache AppConfig{..} = do
, dbRelationships = getOverrideRelationshipsMap rels cRels
, dbRoutines = funcs
, dbRepresentations = reps
+ , dbMediaHandlers = HM.union mHdlers initialMediaHandlers -- the custom handlers will override the initial ones
}
where
schemas = toList configDbSchemas
@@ -169,6 +187,7 @@ removeInternal schemas dbStruct =
HM.filterWithKey (\(QualifiedIdentifier sch _, _) _ -> sch `elem` schemas ) (dbRelationships dbStruct)
, dbRoutines = dbRoutines dbStruct -- procs are only obtained from the exposed schemas, no need to filter them.
, dbRepresentations = dbRepresentations dbStruct -- no need to filter, not directly exposed through the API
+ , dbMediaHandlers = dbMediaHandlers dbStruct
}
where
hasInternalJunction ComputedRelationship{} = False
@@ -1084,6 +1103,81 @@ allViewsKeyDependencies =
having ncol = array_length(array_agg(row(col.attname, view_columns) order by pks_fks.ord), 1)
|]
+initialMediaHandlers :: MediaHandlerMap
+initialMediaHandlers =
+ HM.insert (RelAnyElement, MediaType.MTAny ) BuiltinOvAggJson $
+ HM.insert (RelAnyElement, MediaType.MTApplicationJSON) BuiltinOvAggJson $
+ HM.insert (RelAnyElement, MediaType.MTTextCSV ) BuiltinOvAggCsv $
+ HM.insert (RelAnyElement, MediaType.MTGeoJSON ) BuiltinOvAggGeoJson
+ HM.empty
+
+mediaHandlers :: PgVersion -> Bool -> SQL.Statement [Schema] MediaHandlerMap
+mediaHandlers pgVer =
+ SQL.Statement sql (arrayParam HE.text) decodeMediaHandlers
+ where
+ sql = [q|
+ with
+ all_relations as (
+ select reltype
+ from pg_class
+ where relkind in ('v','r','m','f','p')
+ union
+ select oid
+ from pg_type
+ where typname = 'anyelement'
+ ),
+ media_types as (
+ SELECT
+ t.oid,
+ lower(t.typname) as typname,
+ b.oid as base_oid,
+ b.typname AS basetypname,
+ t.typnamespace
+ FROM pg_type t
+ JOIN pg_type b ON t.typbasetype = b.oid
+ WHERE
+ t.typbasetype <> 0 and
+ t.typname ~* '^[A-Za-z0-9.-]+/[A-Za-z0-9.\+-]+$'
+ )
+ select
+ proc_schema.nspname as handler_schema,
+ proc.proname as handler_name,
+ arg_schema.nspname::text as target_schema,
+ arg_name.typname::text as target_name,
+ media_types.typname as media_type
+ from media_types
+ join pg_proc proc on proc.prorettype = media_types.oid
+ join pg_namespace proc_schema on proc_schema.oid = proc.pronamespace
+ join pg_aggregate agg on agg.aggfnoid = proc.oid
+ join pg_type arg_name on arg_name.oid = proc.proargtypes[0]
+ join pg_namespace arg_schema on arg_schema.oid = arg_name.typnamespace
+ where
+ proc_schema.nspname = ANY($1) and
+ proc.pronargs = 1 and
+ arg_name.oid in (select reltype from all_relations)
+ union
+ select
+ typ_sch.nspname as handler_schema,
+ mtype.typname as handler_name,
+ pro_sch.nspname as target_schema,
+ proname as target_name,
+ mtype.typname as media_type
+ from pg_proc proc
+ join pg_namespace pro_sch on pro_sch.oid = proc.pronamespace
+ join media_types mtype on proc.prorettype = mtype.oid
+ join pg_namespace typ_sch on typ_sch.oid = mtype.typnamespace
+ where NOT proretset
+ |] <> (if pgVer >= pgVersion110 then " AND prokind = 'f'" else " AND NOT (proisagg OR proiswindow)")
+
+decodeMediaHandlers :: HD.Result MediaHandlerMap
+decodeMediaHandlers =
+ HM.fromList . fmap (\(x, y, z) -> ((if isAnyElement y then RelAnyElement else RelId y, z), CustomFunc x) ) <$> HD.rowList caggRow
+ where
+ caggRow = (,,)
+ <$> (QualifiedIdentifier <$> column HD.text <*> column HD.text)
+ <*> (QualifiedIdentifier <$> column HD.text <*> column HD.text)
+ <*> (MediaType.decodeMediaType . encodeUtf8 <$> column HD.text)
+
param :: HE.Value a -> HE.Params a
param = HE.param . HE.nonNullable
diff --git a/src/PostgREST/SchemaCache/Identifiers.hs b/src/PostgREST/SchemaCache/Identifiers.hs
index 8125c278460..80993540ee7 100644
--- a/src/PostgREST/SchemaCache/Identifiers.hs
+++ b/src/PostgREST/SchemaCache/Identifiers.hs
@@ -3,6 +3,8 @@
module PostgREST.SchemaCache.Identifiers
( QualifiedIdentifier(..)
+ , RelIdentifier(..)
+ , isAnyElement
, Schema
, TableName
, FieldName
@@ -17,6 +19,9 @@ import qualified Data.Text as T
import Protolude
+data RelIdentifier = RelId QualifiedIdentifier | RelAnyElement
+ deriving (Eq, Ord, Generic, JSON.ToJSON, JSON.ToJSONKey)
+instance Hashable RelIdentifier
-- | Represents a pg identifier with a prepended schema name "schema.table".
-- When qiSchema is "", the schema is defined by the pg search_path.
@@ -28,6 +33,9 @@ data QualifiedIdentifier = QualifiedIdentifier
instance Hashable QualifiedIdentifier
+isAnyElement :: QualifiedIdentifier -> Bool
+isAnyElement y = QualifiedIdentifier "pg_catalog" "anyelement" == y
+
dumpQi :: QualifiedIdentifier -> Text
dumpQi (QualifiedIdentifier s i) =
(if T.null s then mempty else s <> ".") <> i
diff --git a/src/PostgREST/SchemaCache/Routine.hs b/src/PostgREST/SchemaCache/Routine.hs
index 6e61b007744..572ccc684c2 100644
--- a/src/PostgREST/SchemaCache/Routine.hs
+++ b/src/PostgREST/SchemaCache/Routine.hs
@@ -15,16 +15,20 @@ module PostgREST.SchemaCache.Routine
, funcTableName
, funcReturnsCompositeAlias
, funcReturnsSingle
- , ResultAggregate(..)
+ , MediaHandlerMap
+ , MediaHandler(..)
) where
import Data.Aeson ((.=))
import qualified Data.Aeson as JSON
import qualified Data.HashMap.Strict as HM
import qualified Hasql.Transaction.Sessions as SQL
+import qualified PostgREST.MediaType as MediaType
import PostgREST.SchemaCache.Identifiers (QualifiedIdentifier (..),
- Schema, TableName)
+ RelIdentifier (..), Schema,
+ TableName)
+
import Protolude
@@ -88,12 +92,17 @@ instance Ord Routine where
-- | It uses a HashMap for a faster lookup.
type RoutineMap = HM.HashMap QualifiedIdentifier [Routine]
-data ResultAggregate
- = BuiltinAggJson
- | BuiltinAggSingleJson Bool
+-- | A media handler can be an aggregate over a composite type or a function over a scalar
+data MediaHandler
+ -- non overridable builtins
+ = BuiltinAggSingleJson Bool
| BuiltinAggArrayJsonStrip
- | BuiltinAggGeoJson
- | BuiltinAggCsv
+ -- these builtins are overridable
+ | BuiltinOvAggJson
+ | BuiltinOvAggGeoJson
+ | BuiltinOvAggCsv
+ -- custom
+ | CustomFunc QualifiedIdentifier
| NoAgg
deriving (Eq, Show)
@@ -133,3 +142,5 @@ funcTableName proc = case pdReturnType proc of
SetOf (Composite qi _) -> Just $ qiName qi
Single (Composite qi _) -> Just $ qiName qi
_ -> Nothing
+
+type MediaHandlerMap = HM.HashMap (RelIdentifier, MediaType.MediaType) MediaHandler
diff --git a/test/spec/Feature/OpenApi/RootSpec.hs b/test/spec/Feature/OpenApi/RootSpec.hs
index a1ab1d78bbd..cd8e06dce5c 100644
--- a/test/spec/Feature/OpenApi/RootSpec.hs
+++ b/test/spec/Feature/OpenApi/RootSpec.hs
@@ -13,7 +13,6 @@ spec :: SpecWith ((), Application)
spec =
describe "root spec function" $ do
it "accepts application/openapi+json" $ do
- pendingWith "TBD"
request methodGet "/"
[("Accept","application/openapi+json")] "" `shouldRespondWith`
[json|{
@@ -21,3 +20,12 @@ spec =
"info": {"title": "PostgREST API", "description": "This is a dynamic API generated by PostgREST"}
}|]
{ matchHeaders = ["Content-Type" <:> "application/openapi+json; charset=utf-8"] }
+
+ it "accepts application/json" $ do
+ request methodGet "/"
+ [("Accept","application/json")] "" `shouldRespondWith`
+ [json|{
+ "swagger": "2.0",
+ "info": {"title": "PostgREST API", "description": "This is a dynamic API generated by PostgREST"}
+ }|]
+ { matchHeaders = ["Content-Type" <:> "application/json; charset=utf-8"] }
diff --git a/test/spec/Feature/Query/CustomMediaSpec.hs b/test/spec/Feature/Query/CustomMediaSpec.hs
new file mode 100644
index 00000000000..05737533144
--- /dev/null
+++ b/test/spec/Feature/Query/CustomMediaSpec.hs
@@ -0,0 +1,221 @@
+module Feature.Query.CustomMediaSpec where
+
+import Network.Wai (Application)
+
+import Network.HTTP.Types
+import Network.Wai.Test (SResponse (simpleBody, simpleHeaders, simpleStatus))
+import Test.Hspec
+import Test.Hspec.Wai
+import Test.Hspec.Wai.JSON
+import Text.Heredoc (str)
+
+import Protolude hiding (get)
+import SpecHelper
+
+spec :: SpecWith ((), Application)
+spec = describe "custom media types" $ do
+ context "for tables with aggregate" $ do
+ it "can query if there's an aggregate defined for the table" $ do
+ r <- request methodGet "/lines" (acceptHdrs "application/vnd.twkb") ""
+ liftIO $ do
+ simpleBody r `shouldBe` readFixtureFile "lines.twkb"
+ simpleHeaders r `shouldContain` [("Content-Type", "application/vnd.twkb")]
+
+ it "can query by id if there's an aggregate defined for the table" $ do
+ r <- request methodGet "/lines?id=eq.1" (acceptHdrs "application/vnd.twkb") ""
+ liftIO $ do
+ simpleBody r `shouldBe` readFixtureFile "1.twkb"
+ simpleHeaders r `shouldContain` [("Content-Type", "application/vnd.twkb")]
+
+ it "will fail if there's no aggregate defined for the table" $ do
+ request methodGet "/lines" (acceptHdrs "text/plain") ""
+ `shouldRespondWith`
+ [json| {"code":"PGRST107","details":null,"hint":null,"message":"None of these media types are available: text/plain"} |]
+ { matchStatus = 415
+ , matchHeaders = [matchContentTypeJson]
+ }
+
+ it "can get raw xml output with Accept: text/xml if there's an aggregate defined" $ do
+ request methodGet "/xmltest" (acceptHdrs "text/xml") ""
+ `shouldRespondWith`
+ "