Skip to content

Commit

Permalink
change timezone cache data structure from list to set
Browse files Browse the repository at this point in the history
  • Loading branch information
taimoorzaeem committed Nov 12, 2023
1 parent 964da64 commit 877071f
Show file tree
Hide file tree
Showing 4 changed files with 25 additions and 12 deletions.
30 changes: 21 additions & 9 deletions src/PostgREST/ApiRequest/Preferences.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,13 +16,15 @@ module PostgREST.ApiRequest.Preferences
, PreferRepresentation(..)
, PreferResolution(..)
, PreferTransaction(..)
, PreferTimezone(..)
, fromHeaders
, shouldCount
, prefAppliedHeader
) where

import qualified Data.ByteString.Char8 as BS
import qualified Data.Map as Map
import qualified Data.Set as S
import qualified Network.HTTP.Types.Header as HTTP

import PostgREST.Config.Database (TimezoneNames)
Expand All @@ -39,6 +41,7 @@ import Protolude
-- >>> deriving instance Show PreferTransaction
-- >>> deriving instance Show PreferMissing
-- >>> deriving instance Show PreferHandling
-- >>> deriving instance Show PreferTimezone
-- >>> deriving instance Show Preferences

-- | Preferences recognized by the application.
Expand All @@ -51,14 +54,14 @@ data Preferences
, preferTransaction :: Maybe PreferTransaction
, preferMissing :: Maybe PreferMissing
, preferHandling :: Maybe PreferHandling
, preferTimezone :: Maybe ByteString
, preferTimezone :: Maybe PreferTimezone
, invalidPrefs :: [ByteString]
}

-- |
-- Parse HTTP headers based on RFC7240[1] to identify preferences.
--
-- >>> let sc = ["America/Los_Angeles"]
-- >>> let sc = S.fromList ["America/Los_Angeles"]
--
-- One header with comma-separated values can be used to set multiple preferences:
-- >>> pPrint $ fromHeaders True sc [("Prefer", "resolution=ignore-duplicates, count=exact, timezone=America/Los_Angeles")]
Expand All @@ -70,7 +73,8 @@ data Preferences
-- , preferTransaction = Nothing
-- , preferMissing = Nothing
-- , preferHandling = Nothing
-- , preferTimezone = Just "America/Los_Angeles"
-- , preferTimezone = Just
-- ( PreferTimezone "America/Los_Angeles" )
-- , invalidPrefs = []
-- }
--
Expand Down Expand Up @@ -121,7 +125,7 @@ data Preferences
-- }
--
fromHeaders :: Bool -> TimezoneNames -> [HTTP.Header] -> Preferences
fromHeaders allowTxDbOverride tzNames headers =
fromHeaders allowTxDbOverride acceptedTzNames headers =
Preferences
{ preferResolution = parsePrefs [MergeDuplicates, IgnoreDuplicates]
, preferRepresentation = parsePrefs [Full, None, HeadersOnly]
Expand All @@ -131,24 +135,25 @@ fromHeaders allowTxDbOverride tzNames headers =
, preferMissing = parsePrefs [ApplyDefaults, ApplyNulls]
, preferHandling = parsePrefs [Strict, Lenient]
, preferTimezone = getTimezoneFromPrefs
, invalidPrefs = filter (`notElem` acceptedPrefs) prefs
, invalidPrefs = filter checkPrefs prefs
}
where
mapToHeadVal :: ToHeaderValue a => [a] -> [ByteString]
mapToHeadVal = map toHeaderValue
timezonePrefs = map ((<>) "timezone=" . encodeUtf8) tzNames
acceptedPrefs = mapToHeadVal [MergeDuplicates, IgnoreDuplicates] ++
mapToHeadVal [Full, None, HeadersOnly] ++
mapToHeadVal [SingleObject] ++
mapToHeadVal [ExactCount, PlannedCount, EstimatedCount] ++
mapToHeadVal [Commit, Rollback] ++
mapToHeadVal [ApplyDefaults, ApplyNulls] ++
mapToHeadVal [Strict, Lenient] ++ timezonePrefs
mapToHeadVal [Strict, Lenient]

prefHeaders = filter ((==) HTTP.hPrefer . fst) headers
prefs = fmap BS.strip . concatMap (BS.split ',' . snd) $ prefHeaders

hasTimezone p = BS.take 9 p == "timezone="
getTimezoneFromPrefs = listToMaybe [ BS.drop 9 p | p <- prefs, hasTimezone p && elem p timezonePrefs]
getTimezoneFromPrefs = listToMaybe [ PreferTimezone (BS.drop 9 p) | p <- prefs, hasTimezone p && S.member (BS.drop 9 p) acceptedTzNames]
checkPrefs p = p `notElem` acceptedPrefs && BS.drop 9 p `S.notMember` acceptedTzNames

parsePrefs :: ToHeaderValue a => [a] -> Maybe a
parsePrefs vals =
Expand All @@ -172,7 +177,7 @@ prefAppliedHeader Preferences {preferResolution, preferRepresentation, preferPar
, toHeaderValue <$> preferCount
, toHeaderValue <$> preferTransaction
, toHeaderValue <$> preferHandling
, ("timezone=" <>) <$> preferTimezone
, toHeaderValue <$> preferTimezone
]

-- |
Expand Down Expand Up @@ -265,3 +270,10 @@ data PreferHandling
instance ToHeaderValue PreferHandling where
toHeaderValue Strict = "handling=strict"
toHeaderValue Lenient = "handling=lenient"

-- |
-- Change timezone
newtype PreferTimezone = PreferTimezone ByteString

instance ToHeaderValue PreferTimezone where
toHeaderValue (PreferTimezone tz) = "timezone=" <> tz
2 changes: 1 addition & 1 deletion src/PostgREST/Config/Database.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,7 @@ import Protolude

type RoleSettings = (HM.HashMap ByteString (HM.HashMap ByteString ByteString))
type RoleIsolationLvl = HM.HashMap ByteString SQL.IsolationLevel
type TimezoneNames = [Text] -- cache timezone names for prefer timezone=
type TimezoneNames = Set ByteString -- cache timezone names for prefer timezone=

toIsolationLevel :: (Eq a, IsString a) => a -> SQL.IsolationLevel
toIsolationLevel a = case a of
Expand Down
3 changes: 2 additions & 1 deletion src/PostgREST/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,7 @@ import qualified PostgREST.SchemaCache as SchemaCache

import PostgREST.ApiRequest (ApiRequest (..))
import PostgREST.ApiRequest.Preferences (PreferCount (..),
PreferTimezone (..),
PreferTransaction (..),
Preferences (..),
shouldCount)
Expand Down Expand Up @@ -248,7 +249,7 @@ setPgLocals AppConfig{..} claims role roleSettings ApiRequest{..} = lift $
roleSql = [setConfigWithConstantName ("role", role)]
roleSettingsSql = setConfigWithDynamicName <$> roleSettings
appSettingsSql = setConfigWithDynamicName <$> (join bimap toUtf8 <$> configAppSettings)
timezoneSql = maybe mempty (\tz -> [setConfigWithConstantName ("timezone", tz)]) $ preferTimezone iPreferences
timezoneSql = maybe mempty (\(PreferTimezone tz) -> [setConfigWithConstantName ("timezone", tz)]) $ preferTimezone iPreferences
searchPathSql =
let schemas = escapeIdentList (iSchema : configDbExtraSearchPath) in
setConfigWithConstantName ("search_path", schemas)
Expand Down
2 changes: 1 addition & 1 deletion src/PostgREST/SchemaCache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1190,7 +1190,7 @@ timezones = SQL.Statement sql HE.noParams decodeTimezones
where
sql = "SELECT name FROM pg_timezone_names"
decodeTimezones :: HD.Result TimezoneNames
decodeTimezones = HD.rowList $ column HD.text
decodeTimezones = S.fromList . map encodeUtf8 <$> HD.rowList (column HD.text)

param :: HE.Value a -> HE.Params a
param = HE.param . HE.nonNullable
Expand Down

0 comments on commit 877071f

Please sign in to comment.