Skip to content

Commit

Permalink
Merge branch 'master' into feature/haskell-memory-tests
Browse files Browse the repository at this point in the history
  • Loading branch information
Qu4tro authored May 20, 2019
2 parents aed3668 + 8d8374c commit 222f7a8
Show file tree
Hide file tree
Showing 11 changed files with 71 additions and 40 deletions.
9 changes: 0 additions & 9 deletions .circleci/config.yml
Original file line number Diff line number Diff line change
Expand Up @@ -91,15 +91,6 @@ jobs:
- run:
name: run linter
command: git ls-files | grep '\.l\?hs$' | xargs stack exec -- hlint -X QuasiQuotes -X NoPatternSynonyms "$@"
- run:
name: extra checks
command: |
stack exec -- cabal update
stack exec --no-ghc-package-path -- cabal install --only-d --dry-run
stack exec -- packdeps *.cabal || true
stack exec -- cabal check
stack haddock --no-haddock-deps
stack sdist
- save_cache:
paths:
- "~/.stack"
Expand Down
2 changes: 1 addition & 1 deletion .github/CONTRIBUTING.md
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ your contributions.
then [find your logs](http://blog.endpoint.com/2014/11/dear-postgresql-where-are-my-logs.html).

* If your database schema has changed while the PostgREST server is running,
send the server a `SIGHUP` signal or restart it to ensure the schema cache
[send the server a `SIGUSR1` signal](http://postgrest.org/en/v5.2/admin.html#schema-reloading) or restart it to ensure the schema cache
is not stale. This sometimes fixes apparent bugs.

## Code
Expand Down
14 changes: 14 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ This project adheres to [Semantic Versioning](http://semver.org/).
- #690, Add `?columns` query parameter for faster bulk inserts, also ignores unspecified json keys in a payload - @steve-chavez
- #1239, Add support for resource embedding on materialized views - @vitorbaptista
- #1264, Add support for bulk RPC call - @steve-chavez
- #1278, Add db-pool-timeout config option - @qu4tro

### Fixed

Expand All @@ -19,6 +20,19 @@ This project adheres to [Semantic Versioning](http://semver.org/).
- #1238, Fix PostgreSQL to OpenAPI type mappings for numeric and character types - @fpusch
- #1265, Fix query generated on bulk upsert with an empty array - @qu4tro
- #1273, Fix RPC ignoring unknown arguments by default - @steve-chavez
- #1257, Fix incorrect status when a PATCH request doesn't find rows to change - @qu4tro

### Changed

- #1288, Change server-host default of 127.0.0.1 to !4

### Deprecated

- #1288, Deprecate `.` symbol for disambiguating resource embedding(added in #918). '+' should be used instead. Though '+' is url safe, certain clients might need to encode it to '%2B'.

### Removed

- #1288, Removed support for schema reloading with SIGHUP, SIGUSR1 should be used instead - @steve-chavez

## [5.2.0] - 2018-12-12

Expand Down
2 changes: 1 addition & 1 deletion docker/Dockerfile
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
FROM debian:jessie
FROM debian:stretch-slim

ARG POSTGREST_VERSION

Expand Down
21 changes: 10 additions & 11 deletions main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,7 @@ module Main where


import PostgREST.App (postgrest)
import PostgREST.Config (AppConfig (..),
import PostgREST.Config (AppConfig (..), configPoolTimeout',
prettyVersion, readOptions)
import PostgREST.DbStructure (getDbStructure, getPgVersion)
import PostgREST.Error (encodeError)
Expand Down Expand Up @@ -164,7 +164,7 @@ main = do
--
-- create connection pool with the provided settings, returns either
-- a 'Connection' or a 'ConnectionError'. Does not throw.
pool <- P.acquire (configPool conf, 10, pgSettings)
pool <- P.acquire (configPool conf, configPoolTimeout' conf, pgSettings)
--
-- To be filled in by connectionWorker
refDbStructure <- newIORef Nothing
Expand Down Expand Up @@ -198,15 +198,14 @@ main = do
throwTo mainTid UserInterrupt
) Nothing

forM_ [sigHUP, sigUSR1] $ \sig ->
void $ installHandler sig (
Catch $ connectionWorker
mainTid
pool
(configSchema conf)
refDbStructure
refIsWorkerOn
) Nothing
void $ installHandler sigUSR1 (
Catch $ connectionWorker
mainTid
pool
(configSchema conf)
refDbStructure
refIsWorkerOn
) Nothing
#endif


Expand Down
11 changes: 6 additions & 5 deletions src/PostgREST/ApiRequest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ import qualified Data.Text as T
import qualified Data.Vector as V
import Network.HTTP.Base (urlEncodeVars)
import Network.HTTP.Types.Header (hAuthorization, hCookie)
import Network.HTTP.Types.URI (parseSimpleQuery)
import Network.HTTP.Types.URI (parseSimpleQuery, parseQueryReplacePlus)
import Network.Wai (Request (..))
import Network.Wai.Parse (parseHttpAccept)
import PostgREST.RangeQuery (NonnegRange, rangeRequested, restrictRange, rangeGeq, allRange, rangeLimit, rangeOffset)
Expand Down Expand Up @@ -127,14 +127,15 @@ userApiRequest schema req reqBody
, iOrder = [(toS k, toS $ fromJust v) | (k,v) <- qParams, isJust v, endingIn ["order"] k ]
, iCanonicalQS = toS $ urlEncodeVars
. L.sortBy (comparing fst)
. map (join (***) toS)
. parseSimpleQuery
$ rawQueryString req
. map (join (***) toS . second (fromMaybe BS.empty))
$ queryStringWPlus
, iJWT = tokenStr
, iHeaders = [ (toS $ CI.foldedCase k, toS v) | (k,v) <- hdrs, k /= hAuthorization, k /= hCookie]
, iCookies = maybe [] parseCookiesText $ lookupHeader "Cookie"
}
where
-- queryString with '+' not converted to ' '
queryStringWPlus = parseQueryReplacePlus False $ rawQueryString req
-- rpcQParams = Rpc query params e.g. /rpc/name?param1=val1, similar to filter but with no operator(eq, lt..)
(filters, rpcQParams) =
case action of
Expand Down Expand Up @@ -201,7 +202,7 @@ userApiRequest schema req reqBody
path = pathInfo req
method = requestMethod req
hdrs = requestHeaders req
qParams = [(toS k, v)|(k,v) <- queryString req]
qParams = [(toS k, v)|(k,v) <- queryStringWPlus]
lookupHeader = flip lookup hdrs
hasPrefer :: Text -> Bool
hasPrefer val = any (\(h,v) -> h == "Prefer" && val `elem` split v) hdrs
Expand Down
13 changes: 11 additions & 2 deletions src/PostgREST/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,6 +19,7 @@ module PostgREST.Config ( prettyVersion
, readOptions
, corsPolicy
, AppConfig (..)
, configPoolTimeout'
)
where

Expand Down Expand Up @@ -73,6 +74,7 @@ data AppConfig = AppConfig {
, configJwtAudience :: Maybe StringOrURI

, configPool :: Int
, configPoolTimeout :: Int
, configMaxRows :: Maybe Integer
, configReqCheck :: Maybe Text
, configQuiet :: Bool
Expand All @@ -81,6 +83,11 @@ data AppConfig = AppConfig {
, configExtraSearchPath :: [Text]
}

configPoolTimeout' :: (Fractional a) => AppConfig -> a
configPoolTimeout' =
fromRational . toRational . configPoolTimeout


defaultCorsPolicy :: CorsResourcePolicy
defaultCorsPolicy = CorsResourcePolicy Nothing
["GET", "POST", "PATCH", "PUT", "DELETE", "OPTIONS"] ["Authorization"] Nothing
Expand Down Expand Up @@ -130,12 +137,13 @@ readOptions = do
<*> C.key "db-anon-role"
<*> (mfilter (/= "") <$> C.key "server-proxy-uri")
<*> C.key "db-schema"
<*> (fromMaybe "127.0.0.1" . mfilter (/= "") <$> C.key "server-host")
<*> (fromMaybe "!4" . mfilter (/= "") <$> C.key "server-host")
<*> (fromMaybe 3000 . join . fmap coerceInt <$> C.key "server-port")
<*> (fmap encodeUtf8 . mfilter (/= "") <$> C.key "jwt-secret")
<*> (fromMaybe False . join . fmap coerceBool <$> C.key "secret-is-base64")
<*> parseJwtAudience "jwt-aud"
<*> (fromMaybe 10 . join . fmap coerceInt <$> C.key "db-pool")
<*> (fromMaybe 10 . join . fmap coerceInt <$> C.key "db-pool-timeout")
<*> (join . fmap coerceInt <$> C.key "max-rows")
<*> (mfilter (/= "") <$> C.key "pre-request")
<*> pure False
Expand Down Expand Up @@ -208,8 +216,9 @@ readOptions = do
|db-schema = "public" # this schema gets added to the search_path of every request
|db-anon-role = "postgres"
|db-pool = 10
|db-pool-timeout = 10
|
|server-host = "127.0.0.1"
|server-host = "!4"
|server-port = 3000
|
|## base url for swagger output
Expand Down
5 changes: 4 additions & 1 deletion src/PostgREST/Parsers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,10 @@ pRelationSelect :: Parser SelectItem
pRelationSelect = lexeme $ try ( do
alias <- optionMaybe ( try(pFieldName <* aliasSeparator) )
fld <- pField
relationDetail <- optionMaybe ( try( char '.' *> pFieldName ) )
relationDetail <- optionMaybe (
try ( char '+' *> pFieldName ) <|>
try ( char '.' *> pFieldName ) -- TODO deprecated, remove in next major version
)

return (fld, Nothing, alias, relationDetail)
)
Expand Down
5 changes: 5 additions & 0 deletions stack.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,13 @@ extra-deps:
- text-builder-0.5.1.1
- jose-0.7.0.0
- postgresql-libpq-0.9.4.1
- http-types-0.12.3
- weigh-0.0.14
- wai-middleware-static-0.8.2
ghc-options:
postgrest: -O2 -Werror -Wall -fwarn-identities -fno-warn-redundant-constraints
nix:
packages: [postgresql, zlib]
# only added because of hjsonschema conflict with http-types
# once hjsonschema upper bounding on http-types is solved it can be removed
allow-newer: true
27 changes: 18 additions & 9 deletions test/Feature/QuerySpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -443,31 +443,40 @@ spec = do

describe "path fixed" $ do
it "works when requesting children 2 levels" $
get "/clients?id=eq.1&select=id,projects:projects.client_id(id,tasks(id))" `shouldRespondWith`
get "/clients?id=eq.1&select=id,projects:projects%2Bclient_id(id,tasks(id))" `shouldRespondWith`
[json|[{"id":1,"projects":[{"id":1,"tasks":[{"id":1},{"id":2}]},{"id":2,"tasks":[{"id":3},{"id":4}]}]}]|]
{ matchHeaders = [matchContentTypeJson] }

it "works with parent relation" $
get "/message?select=id,body,sender:person.sender(name),recipient:person.recipient(name)&id=lt.4" `shouldRespondWith`
get "/message?select=id,body,sender:person%2Bsender(name),recipient:person%2Brecipient(name)&id=lt.4" `shouldRespondWith`
[json|
[{"id":1,"body":"Hello Jane","sender":{"name":"John"},"recipient":{"name":"Jane"}},
{"id":2,"body":"Hi John","sender":{"name":"Jane"},"recipient":{"name":"John"}},
{"id":3,"body":"How are you doing?","sender":{"name":"John"},"recipient":{"name":"Jane"}}] |]
{ matchHeaders = [matchContentTypeJson] }

it "works with a parent view relation" $
get "/message?select=id,body,sender:person_detail.sender(name,sent),recipient:person_detail.recipient(name,received)&id=lt.4" `shouldRespondWith`
get "/message?select=id,body,sender:person_detail%2Bsender(name,sent),recipient:person_detail%2Brecipient(name,received)&id=lt.4" `shouldRespondWith`
[json|
[{"id":1,"body":"Hello Jane","sender":{"name":"John","sent":2},"recipient":{"name":"Jane","received":2}},
{"id":2,"body":"Hi John","sender":{"name":"Jane","sent":1},"recipient":{"name":"John","received":1}},
{"id":3,"body":"How are you doing?","sender":{"name":"John","sent":2},"recipient":{"name":"Jane","received":2}}] |]
{ matchHeaders = [matchContentTypeJson] }

it "works with many<->many relation" $
get "/tasks?select=id,users:users.users_tasks(id)" `shouldRespondWith`
get "/tasks?select=id,users:users%2Busers_tasks(id)" `shouldRespondWith`
[json|[{"id":1,"users":[{"id":1},{"id":3}]},{"id":2,"users":[{"id":1}]},{"id":3,"users":[{"id":1}]},{"id":4,"users":[{"id":1}]},{"id":5,"users":[{"id":2},{"id":3}]},{"id":6,"users":[{"id":2}]},{"id":7,"users":[{"id":2}]},{"id":8,"users":[]}]|]
{ matchHeaders = [matchContentTypeJson] }

describe "old dot '.' symbol, deprecated" $
it "still works" $ do
get "/clients?id=eq.1&select=id,projects:projects.client_id(id,tasks(id))" `shouldRespondWith`
[json|[{"id":1,"projects":[{"id":1,"tasks":[{"id":1},{"id":2}]},{"id":2,"tasks":[{"id":3},{"id":4}]}]}]|]
{ matchHeaders = [matchContentTypeJson] }
get "/tasks?select=id,users:users.users_tasks(id)" `shouldRespondWith`
[json|[{"id":1,"users":[{"id":1},{"id":3}]},{"id":2,"users":[{"id":1}]},{"id":3,"users":[{"id":1}]},{"id":4,"users":[{"id":1}]},{"id":5,"users":[{"id":2},{"id":3}]},{"id":6,"users":[{"id":2}]},{"id":7,"users":[{"id":2}]},{"id":8,"users":[]}]|]
{ matchHeaders = [matchContentTypeJson] }

describe "aliased embeds" $ do
it "works with child relation" $
get "/space?select=id,zones:zone(id,name),stores:zone(id,name)&zones.zone_type_id=eq.2&stores.zone_type_id=eq.3" `shouldRespondWith`
Expand Down Expand Up @@ -536,7 +545,7 @@ spec = do
{ matchHeaders = [matchContentTypeJson] }

it "embeds childs recursively" $
get "/family_tree?id=eq.1&select=id,name, childs:family_tree.parent(id,name,childs:family_tree.parent(id,name))" `shouldRespondWith`
get "/family_tree?id=eq.1&select=id,name, childs:family_tree%2Bparent(id,name,childs:family_tree%2Bparent(id,name))" `shouldRespondWith`
[json|[{
"id": "1", "name": "Parental Unit", "childs": [
{ "id": "2", "name": "Kid One", "childs": [ { "id": "4", "name": "Grandkid One" } ] },
Expand All @@ -545,7 +554,7 @@ spec = do
}]|] { matchHeaders = [matchContentTypeJson] }

it "embeds parent and then embeds childs" $
get "/family_tree?id=eq.2&select=id,name,parent(id,name,childs:family_tree.parent(id,name))" `shouldRespondWith`
get "/family_tree?id=eq.2&select=id,name,parent(id,name,childs:family_tree%2Bparent(id,name))" `shouldRespondWith`
[json|[{
"id": "2", "name": "Kid One", "parent": {
"id": "1", "name": "Parental Unit", "childs": [ { "id": "2", "name": "Kid One" }, { "id": "3", "name": "Kid Two"} ]
Expand All @@ -568,7 +577,7 @@ spec = do
}]|] { matchHeaders = [matchContentTypeJson] }

it "embeds childs" $ do
get "/organizations?select=id,name,refereeds:organizations.referee(id,name)&id=eq.1" `shouldRespondWith`
get "/organizations?select=id,name,refereeds:organizations%2Breferee(id,name)&id=eq.1" `shouldRespondWith`
[json|[{
"id": 1, "name": "Referee Org",
"refereeds": [
Expand All @@ -582,7 +591,7 @@ spec = do
}
]
}]|] { matchHeaders = [matchContentTypeJson] }
get "/organizations?select=id,name,auditees:organizations.auditor(id,name)&id=eq.2" `shouldRespondWith`
get "/organizations?select=id,name,auditees:organizations%2Bauditor(id,name)&id=eq.2" `shouldRespondWith`
[json|[{
"id": 2, "name": "Auditor Org",
"auditees": [
Expand Down Expand Up @@ -616,7 +625,7 @@ spec = do
"manager":{"name":"Referee Manager"}}}
}]|] { matchHeaders = [matchContentTypeJson] }

get "/organizations?select=name,manager(name),auditees:organizations.auditor(name,manager(name),refereeds:organizations.referee(name,manager(name)))&id=eq.2" `shouldRespondWith`
get "/organizations?select=name,manager(name),auditees:organizations%2Bauditor(name,manager(name),refereeds:organizations%2Breferee(name,manager(name)))&id=eq.2" `shouldRespondWith`
[json|[{
"name":"Auditor Org",
"manager":{"name":"Auditor Manager"},
Expand Down
2 changes: 1 addition & 1 deletion test/SpecHelper.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,7 @@ _baseCfg = -- Connection Settings
-- Jwt settings
(Just $ encodeUtf8 "reallyreallyreallyreallyverysafe") False Nothing
-- Connection Modifiers
10 Nothing (Just "test.switch_role")
10 10 Nothing (Just "test.switch_role")
-- Debug Settings
True
[ ("app.settings.app_host", "localhost")
Expand Down

0 comments on commit 222f7a8

Please sign in to comment.