Skip to content

Commit

Permalink
fix: compilation on Ubuntu, GHC 9.0.2 compat
Browse files Browse the repository at this point in the history
  • Loading branch information
steve-chavez committed Jun 21, 2023
1 parent ed49eab commit e3a11fc
Show file tree
Hide file tree
Showing 2 changed files with 5 additions and 5 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ This project adheres to [Semantic Versioning](http://semver.org/).
### Fixed

- #2821, Fix OPTIONS not accepting all available media types - @steve-chavez
- #2834, Fix compilation on Ubuntu by being compatible with GHC 9.0.2 - @steve-chavez

## [11.1.0] - 2023-06-07

Expand Down
9 changes: 4 additions & 5 deletions src/PostgREST/Plan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ resource.
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE RecordWildCards #-}

module PostgREST.Plan
Expand Down Expand Up @@ -503,10 +502,10 @@ updateNode f (targetNodeName:remainingPath, a) (Right (Node rootNode forest)) =
findNode = find (\(Node ReadPlan{relName, relAlias} _) -> relName == targetNodeName || relAlias == Just targetNodeName) forest

mutatePlan :: Mutation -> QualifiedIdentifier -> ApiRequest -> SchemaCache -> ReadPlanTree -> Either Error MutatePlan
mutatePlan mutation qi ApiRequest{iPreferences=preferences, ..} sCache readReq = mapLeft ApiRequestError $
mutatePlan mutation qi ApiRequest{iPreferences=Preferences{..}, ..} sCache readReq = mapLeft ApiRequestError $
case mutation of
MutationCreate ->
mapRight (\typedColumns -> Insert qi typedColumns body ((,) <$> preferences.preferResolution <*> Just confCols) [] returnings pkCols applyDefaults) typedColumnsOrError
mapRight (\typedColumns -> Insert qi typedColumns body ((,) <$> preferResolution <*> Just confCols) [] returnings pkCols applyDefaults) typedColumnsOrError
MutationUpdate ->
mapRight (\typedColumns -> Update qi typedColumns body combinedLogic iTopLevelRange rootOrder returnings applyDefaults) typedColumnsOrError
MutationSingleUpsert ->
Expand All @@ -524,7 +523,7 @@ mutatePlan mutation qi ApiRequest{iPreferences=preferences, ..} sCache readReq =
confCols = fromMaybe pkCols qsOnConflict
QueryParams.QueryParams{..} = iQueryParams
returnings =
if preferences.preferRepresentation == None
if preferRepresentation == None
then []
else inferColsEmbedNeeds readReq pkCols
pkCols = maybe mempty tablePKCols $ HM.lookup qi $ dbTables sCache
Expand All @@ -534,7 +533,7 @@ mutatePlan mutation qi ApiRequest{iPreferences=preferences, ..} sCache readReq =
body = payRaw <$> iPayload -- the body is assumed to be json at this stage(ApiRequest validates)
tbl = HM.lookup qi $ dbTables sCache
typedColumnsOrError = resolveOrError tbl `traverse` S.toList iColumns
applyDefaults = preferences.preferMissing == Just ApplyDefaults
applyDefaults = preferMissing == Just ApplyDefaults

resolveOrError :: Maybe Table -> FieldName -> Either ApiRequestError TypedField
resolveOrError Nothing _ = Left NotFound
Expand Down

0 comments on commit e3a11fc

Please sign in to comment.