{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}
module PostgREST.Config
( AppConfig (..)
, Environment
, JSPath
, JSPathExp(..)
, LogLevel(..)
, OpenAPIMode(..)
, Proxy(..)
, toText
, isMalformedProxyUri
, readAppConfig
, readPGRSTEnvironment
, toURI
, parseSecret
) where
import qualified Crypto.JOSE.Types as JOSE
import qualified Crypto.JWT as JWT
import qualified Data.Aeson as JSON
import qualified Data.ByteString as B
import qualified Data.ByteString.Base64 as B64
import qualified Data.ByteString.Char8 as BS
import qualified Data.Configurator as C
import qualified Data.Map.Strict as M
import qualified Data.Text as T
import qualified GHC.Show (show)
import Control.Lens (preview)
import Control.Monad (fail)
import Crypto.JWT (JWK, JWKSet, StringOrURI, stringOrUri)
import Data.Aeson (encode, toJSON)
import Data.Either.Combinators (mapLeft)
import Data.List (lookup)
import Data.List.NonEmpty (fromList, toList)
import Data.Maybe (fromJust)
import Data.Scientific (floatingOrInteger)
import Data.Time.Clock (NominalDiffTime)
import Numeric (readOct, showOct)
import System.Environment (getEnvironment)
import System.Posix.Types (FileMode)
import PostgREST.Config.JSPath (JSPath, JSPathExp (..),
pRoleClaimKey)
import PostgREST.Config.Proxy (Proxy (..),
isMalformedProxyUri, toURI)
import PostgREST.DbStructure.Identifiers (QualifiedIdentifier, toQi)
import Protolude hiding (Proxy, toList, toS)
import Protolude.Conv (toS)
data AppConfig = AppConfig
{ AppConfig -> [(Text, Text)]
configAppSettings :: [(Text, Text)]
, AppConfig -> Text
configDbAnonRole :: Text
, AppConfig -> Text
configDbChannel :: Text
, AppConfig -> Bool
configDbChannelEnabled :: Bool
, :: [Text]
, AppConfig -> Maybe Integer
configDbMaxRows :: Maybe Integer
, AppConfig -> Int
configDbPoolSize :: Int
, AppConfig -> NominalDiffTime
configDbPoolTimeout :: NominalDiffTime
, AppConfig -> Maybe QualifiedIdentifier
configDbPreRequest :: Maybe QualifiedIdentifier
, AppConfig -> Bool
configDbPreparedStatements :: Bool
, AppConfig -> Maybe QualifiedIdentifier
configDbRootSpec :: Maybe QualifiedIdentifier
, AppConfig -> NonEmpty Text
configDbSchemas :: NonEmpty Text
, AppConfig -> Bool
configDbConfig :: Bool
, AppConfig -> Bool
configDbTxAllowOverride :: Bool
, AppConfig -> Bool
configDbTxRollbackAll :: Bool
, AppConfig -> Text
configDbUri :: Text
, AppConfig -> Maybe FilePath
configFilePath :: Maybe FilePath
, AppConfig -> Maybe JWKSet
configJWKS :: Maybe JWKSet
, AppConfig -> Maybe StringOrURI
configJwtAudience :: Maybe StringOrURI
, AppConfig -> JSPath
configJwtRoleClaimKey :: JSPath
, AppConfig -> Maybe ByteString
configJwtSecret :: Maybe B.ByteString
, AppConfig -> Bool
configJwtSecretIsBase64 :: Bool
, AppConfig -> LogLevel
configLogLevel :: LogLevel
, AppConfig -> OpenAPIMode
configOpenApiMode :: OpenAPIMode
, AppConfig -> Maybe Text
configOpenApiServerProxyUri :: Maybe Text
, AppConfig -> [ByteString]
configRawMediaTypes :: [B.ByteString]
, AppConfig -> Text
configServerHost :: Text
, AppConfig -> Int
configServerPort :: Int
, AppConfig -> Maybe FilePath
configServerUnixSocket :: Maybe FilePath
, AppConfig -> FileMode
configServerUnixSocketMode :: FileMode
}
data LogLevel = LogCrit | LogError | LogWarn | LogInfo
instance Show LogLevel where
show :: LogLevel -> FilePath
show LogLevel
LogCrit = FilePath
"crit"
show LogLevel
LogError = FilePath
"error"
show LogLevel
LogWarn = FilePath
"warn"
show LogLevel
LogInfo = FilePath
"info"
data OpenAPIMode = OAFollowPriv | OAIgnorePriv | OADisabled
deriving OpenAPIMode -> OpenAPIMode -> Bool
(OpenAPIMode -> OpenAPIMode -> Bool)
-> (OpenAPIMode -> OpenAPIMode -> Bool) -> Eq OpenAPIMode
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OpenAPIMode -> OpenAPIMode -> Bool
$c/= :: OpenAPIMode -> OpenAPIMode -> Bool
== :: OpenAPIMode -> OpenAPIMode -> Bool
$c== :: OpenAPIMode -> OpenAPIMode -> Bool
Eq
instance Show OpenAPIMode where
show :: OpenAPIMode -> FilePath
show OpenAPIMode
OAFollowPriv = FilePath
"follow-privileges"
show OpenAPIMode
OAIgnorePriv = FilePath
"ignore-privileges"
show OpenAPIMode
OADisabled = FilePath
"disabled"
toText :: AppConfig -> Text
toText :: AppConfig -> Text
toText AppConfig
conf =
[Text] -> Text
unlines ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$ (\(Text
k, Text
v) -> Text
k Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" = " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
v) ((Text, Text) -> Text) -> [(Text, Text)] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [(Text, Text)]
pgrstSettings [(Text, Text)] -> [(Text, Text)] -> [(Text, Text)]
forall a. [a] -> [a] -> [a]
++ [(Text, Text)]
appSettings
where
pgrstSettings :: [(Text, Text)]
pgrstSettings = (\(Text
k, AppConfig -> Text
v) -> (Text
k, AppConfig -> Text
v AppConfig
conf)) ((Text, AppConfig -> Text) -> (Text, Text))
-> [(Text, AppConfig -> Text)] -> [(Text, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
[(Text
"db-anon-role", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Text
configDbAnonRole)
,(Text
"db-channel", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Text
configDbChannel)
,(Text
"db-channel-enabled", Text -> Text
T.toLower (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Bool -> Text) -> (AppConfig -> Bool) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Bool
configDbChannelEnabled)
,(Text
"db-extra-search-path", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> (AppConfig -> [Text]) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> [Text]
configDbExtraSearchPath)
,(Text
"db-max-rows", Text -> (Integer -> Text) -> Maybe Integer -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
"\"\"" Integer -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Maybe Integer -> Text)
-> (AppConfig -> Maybe Integer) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Maybe Integer
configDbMaxRows)
,(Text
"db-pool", Int -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Int -> Text) -> (AppConfig -> Int) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Int
configDbPoolSize)
,(Text
"db-pool-timeout", Integer -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Integer -> Text) -> (AppConfig -> Integer) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NominalDiffTime -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
floor (NominalDiffTime -> Integer)
-> (AppConfig -> NominalDiffTime) -> AppConfig -> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> NominalDiffTime
configDbPoolTimeout)
,(Text
"db-pre-request", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text
-> (QualifiedIdentifier -> Text)
-> Maybe QualifiedIdentifier
-> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty QualifiedIdentifier -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Maybe QualifiedIdentifier -> Text)
-> (AppConfig -> Maybe QualifiedIdentifier) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Maybe QualifiedIdentifier
configDbPreRequest)
,(Text
"db-prepared-statements", Text -> Text
T.toLower (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Bool -> Text) -> (AppConfig -> Bool) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Bool
configDbPreparedStatements)
,(Text
"db-root-spec", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text
-> (QualifiedIdentifier -> Text)
-> Maybe QualifiedIdentifier
-> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty QualifiedIdentifier -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Maybe QualifiedIdentifier -> Text)
-> (AppConfig -> Maybe QualifiedIdentifier) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Maybe QualifiedIdentifier
configDbRootSpec)
,(Text
"db-schemas", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
"," ([Text] -> Text) -> (AppConfig -> [Text]) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty Text -> [Text]
forall a. NonEmpty a -> [a]
toList (NonEmpty Text -> [Text])
-> (AppConfig -> NonEmpty Text) -> AppConfig -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> NonEmpty Text
configDbSchemas)
,(Text
"db-config", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.toLower (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Bool -> Text) -> (AppConfig -> Bool) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Bool
configDbConfig)
,(Text
"db-tx-end", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Text
forall p. IsString p => AppConfig -> p
showTxEnd)
,(Text
"db-uri", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Text
configDbUri)
,(Text
"jwt-aud", ByteString -> Text
forall a b. StringConv a b => a -> b
toS (ByteString -> Text)
-> (AppConfig -> ByteString) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> ByteString
forall a. ToJSON a => a -> ByteString
encode (Value -> ByteString)
-> (AppConfig -> Value) -> AppConfig -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> (StringOrURI -> Value) -> Maybe StringOrURI -> Value
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Value
"" StringOrURI -> Value
forall a. ToJSON a => a -> Value
toJSON (Maybe StringOrURI -> Value)
-> (AppConfig -> Maybe StringOrURI) -> AppConfig -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Maybe StringOrURI
configJwtAudience)
,(Text
"jwt-role-claim-key", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> [Text] -> Text
T.intercalate Text
forall a. Monoid a => a
mempty ([Text] -> Text) -> (AppConfig -> [Text]) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (JSPathExp -> Text) -> JSPath -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap JSPathExp -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (JSPath -> [Text]) -> (AppConfig -> JSPath) -> AppConfig -> [Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> JSPath
configJwtRoleClaimKey)
,(Text
"jwt-secret", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
forall a b. StringConv a b => a -> b
toS (ByteString -> Text)
-> (AppConfig -> ByteString) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> ByteString
showJwtSecret)
,(Text
"jwt-secret-is-base64", Text -> Text
T.toLower (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Bool -> Text) -> (AppConfig -> Bool) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Bool
configJwtSecretIsBase64)
,(Text
"log-level", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LogLevel -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (LogLevel -> Text) -> (AppConfig -> LogLevel) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> LogLevel
configLogLevel)
,(Text
"openapi-mode", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OpenAPIMode -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (OpenAPIMode -> Text)
-> (AppConfig -> OpenAPIMode) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> OpenAPIMode
configOpenApiMode)
,(Text
"openapi-server-proxy-uri", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
forall a. Monoid a => a
mempty (Maybe Text -> Text)
-> (AppConfig -> Maybe Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Maybe Text
configOpenApiServerProxyUri)
,(Text
"raw-media-types", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
forall a b. StringConv a b => a -> b
toS (ByteString -> Text)
-> (AppConfig -> ByteString) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString] -> ByteString
B.intercalate ByteString
"," ([ByteString] -> ByteString)
-> (AppConfig -> [ByteString]) -> AppConfig -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> [ByteString]
configRawMediaTypes)
,(Text
"server-host", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Text
configServerHost)
,(Text
"server-port", Int -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show (Int -> Text) -> (AppConfig -> Int) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Int
configServerPort)
,(Text
"server-unix-socket", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> (FilePath -> Text) -> Maybe FilePath -> Text
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Text
forall a. Monoid a => a
mempty FilePath -> Text
T.pack (Maybe FilePath -> Text)
-> (AppConfig -> Maybe FilePath) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> Maybe FilePath
configServerUnixSocket)
,(Text
"server-unix-socket-mode", Text -> Text
q (Text -> Text) -> (AppConfig -> Text) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> Text
T.pack (FilePath -> Text) -> (AppConfig -> FilePath) -> AppConfig -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AppConfig -> FilePath
showSocketMode)
]
appSettings :: [(Text, Text)]
appSettings = (Text -> Text) -> (Text, Text) -> (Text, Text)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second Text -> Text
q ((Text, Text) -> (Text, Text)) -> [(Text, Text)] -> [(Text, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AppConfig -> [(Text, Text)]
configAppSettings AppConfig
conf
q :: Text -> Text
q Text
s = Text
"\"" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> Text -> Text -> Text
T.replace Text
"\"" Text
"\\\"" Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\""
showTxEnd :: AppConfig -> p
showTxEnd AppConfig
c = case (AppConfig -> Bool
configDbTxRollbackAll AppConfig
c, AppConfig -> Bool
configDbTxAllowOverride AppConfig
c) of
( Bool
False, Bool
False ) -> p
"commit"
( Bool
False, Bool
True ) -> p
"commit-allow-override"
( Bool
True , Bool
False ) -> p
"rollback"
( Bool
True , Bool
True ) -> p
"rollback-allow-override"
showJwtSecret :: AppConfig -> ByteString
showJwtSecret AppConfig
c
| AppConfig -> Bool
configJwtSecretIsBase64 AppConfig
c = ByteString -> ByteString
B64.encode ByteString
secret
| Bool
otherwise = ByteString -> ByteString
forall a b. StringConv a b => a -> b
toS ByteString
secret
where
secret :: ByteString
secret = ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
forall a. Monoid a => a
mempty (Maybe ByteString -> ByteString) -> Maybe ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ AppConfig -> Maybe ByteString
configJwtSecret AppConfig
c
showSocketMode :: AppConfig -> FilePath
showSocketMode AppConfig
c = FileMode -> ShowS
forall a. (Integral a, Show a) => a -> ShowS
showOct (AppConfig -> FileMode
configServerUnixSocketMode AppConfig
c) FilePath
forall a. Monoid a => a
mempty
class JustIfMaybe a b where
justIfMaybe :: a -> b
instance JustIfMaybe a a where
justIfMaybe :: a -> a
justIfMaybe a
a = a
a
instance JustIfMaybe a (Maybe a) where
justIfMaybe :: a -> Maybe a
justIfMaybe a
a = a -> Maybe a
forall a. a -> Maybe a
Just a
a
readAppConfig :: [(Text, Text)] -> Maybe FilePath -> Maybe Text -> IO (Either Text AppConfig)
readAppConfig :: [(Text, Text)]
-> Maybe FilePath -> Maybe Text -> IO (Either Text AppConfig)
readAppConfig [(Text, Text)]
dbSettings Maybe FilePath
optPath Maybe Text
prevDbUri = do
Environment
env <- IO Environment
readPGRSTEnvironment
Either SomeException (Map Text Value)
conf <- IO (Either SomeException (Map Text Value))
-> (FilePath -> IO (Either SomeException (Map Text Value)))
-> Maybe FilePath
-> IO (Either SomeException (Map Text Value))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Either SomeException (Map Text Value)
-> IO (Either SomeException (Map Text Value))
forall (m :: * -> *) a. Monad m => a -> m a
return (Either SomeException (Map Text Value)
-> IO (Either SomeException (Map Text Value)))
-> Either SomeException (Map Text Value)
-> IO (Either SomeException (Map Text Value))
forall a b. (a -> b) -> a -> b
$ Map Text Value -> Either SomeException (Map Text Value)
forall a b. b -> Either a b
Right Map Text Value
forall k a. Map k a
M.empty) FilePath -> IO (Either SomeException (Map Text Value))
loadConfig Maybe FilePath
optPath
case Parser (Map Text Value) AppConfig
-> Map Text Value -> Either Text AppConfig
forall a b. Parser a b -> a -> Either Text b
C.runParser (Maybe FilePath
-> Environment
-> [(Text, Text)]
-> Parser (Map Text Value) AppConfig
parser Maybe FilePath
optPath Environment
env [(Text, Text)]
dbSettings) (Map Text Value -> Either Text AppConfig)
-> Either Text (Map Text Value) -> Either Text AppConfig
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< (SomeException -> Text)
-> Either SomeException (Map Text Value)
-> Either Text (Map Text Value)
forall a c b. (a -> c) -> Either a b -> Either c b
mapLeft SomeException -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show Either SomeException (Map Text Value)
conf of
Left Text
err ->
Either Text AppConfig -> IO (Either Text AppConfig)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either Text AppConfig -> IO (Either Text AppConfig))
-> (Text -> Either Text AppConfig)
-> Text
-> IO (Either Text AppConfig)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Either Text AppConfig
forall a b. a -> Either a b
Left (Text -> IO (Either Text AppConfig))
-> Text -> IO (Either Text AppConfig)
forall a b. (a -> b) -> a -> b
$ Text
"Error in config " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
err
Right AppConfig
parsedConfig ->
AppConfig -> Either Text AppConfig
forall a b. b -> Either a b
Right (AppConfig -> Either Text AppConfig)
-> IO AppConfig -> IO (Either Text AppConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AppConfig -> IO AppConfig
decodeLoadFiles AppConfig
parsedConfig
where
loadConfig :: FilePath -> IO (Either SomeException C.Config)
loadConfig :: FilePath -> IO (Either SomeException (Map Text Value))
loadConfig = IO (Map Text Value) -> IO (Either SomeException (Map Text Value))
forall e a. Exception e => IO a -> IO (Either e a)
try (IO (Map Text Value) -> IO (Either SomeException (Map Text Value)))
-> (FilePath -> IO (Map Text Value))
-> FilePath
-> IO (Either SomeException (Map Text Value))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO (Map Text Value)
C.load
decodeLoadFiles :: AppConfig -> IO AppConfig
decodeLoadFiles :: AppConfig -> IO AppConfig
decodeLoadFiles AppConfig
parsedConfig =
AppConfig -> AppConfig
decodeJWKS (AppConfig -> AppConfig) -> IO AppConfig -> IO AppConfig
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
(AppConfig -> IO AppConfig
decodeSecret (AppConfig -> IO AppConfig) -> IO AppConfig -> IO AppConfig
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< AppConfig -> IO AppConfig
readSecretFile (AppConfig -> IO AppConfig) -> IO AppConfig -> IO AppConfig
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Maybe Text -> AppConfig -> IO AppConfig
readDbUriFile Maybe Text
prevDbUri AppConfig
parsedConfig)
parser :: Maybe FilePath -> Environment -> [(Text, Text)] -> C.Parser C.Config AppConfig
parser :: Maybe FilePath
-> Environment
-> [(Text, Text)]
-> Parser (Map Text Value) AppConfig
parser Maybe FilePath
optPath Environment
env [(Text, Text)]
dbSettings =
[(Text, Text)]
-> Text
-> Text
-> Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig
AppConfig
([(Text, Text)]
-> Text
-> Text
-> Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) [(Text, Text)]
-> Parser
(Map Text Value)
(Text
-> Text
-> Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) [(Text, Text)]
parseAppSettings Text
"app.settings"
Parser
(Map Text Value)
(Text
-> Text
-> Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Text
-> Parser
(Map Text Value)
(Text
-> Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser (Map Text Value) Text
reqString Text
"db-anon-role"
Parser
(Map Text Value)
(Text
-> Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Text
-> Parser
(Map Text Value)
(Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"pgrst" (Maybe Text -> Text)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"db-channel")
Parser
(Map Text Value)
(Bool
-> [Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Bool
-> Parser
(Map Text Value)
([Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool)
-> Parser (Map Text Value) (Maybe Bool)
-> Parser (Map Text Value) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Bool)
optBool Text
"db-channel-enabled")
Parser
(Map Text Value)
([Text]
-> Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) [Text]
-> Parser
(Map Text Value)
(Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([Text] -> (Value -> [Text]) -> Maybe Value -> [Text]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Text
"public"] Value -> [Text]
splitOnCommas (Maybe Value -> [Text])
-> Parser (Map Text Value) (Maybe Value)
-> Parser (Map Text Value) [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Value)
optValue Text
"db-extra-search-path")
Parser
(Map Text Value)
(Maybe Integer
-> Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe Integer)
-> Parser
(Map Text Value)
(Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Map Text Value) (Maybe Integer)
-> Parser (Map Text Value) (Maybe Integer)
-> Parser (Map Text Value) (Maybe Integer)
forall a.
Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
optWithAlias (Text -> Parser (Map Text Value) (Maybe Integer)
forall i.
(Read i, Integral i) =>
Text -> Parser (Map Text Value) (Maybe i)
optInt Text
"db-max-rows")
(Text -> Parser (Map Text Value) (Maybe Integer)
forall i.
(Read i, Integral i) =>
Text -> Parser (Map Text Value) (Maybe i)
optInt Text
"max-rows")
Parser
(Map Text Value)
(Int
-> NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Int
-> Parser
(Map Text Value)
(NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
10 (Maybe Int -> Int)
-> Parser (Map Text Value) (Maybe Int)
-> Parser (Map Text Value) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Int)
forall i.
(Read i, Integral i) =>
Text -> Parser (Map Text Value) (Maybe i)
optInt Text
"db-pool")
Parser
(Map Text Value)
(NominalDiffTime
-> Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) NominalDiffTime
-> Parser
(Map Text Value)
(Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Integer -> NominalDiffTime
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Integer -> NominalDiffTime)
-> (Maybe Integer -> Integer) -> Maybe Integer -> NominalDiffTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Maybe Integer -> Integer
forall a. a -> Maybe a -> a
fromMaybe Integer
10 (Maybe Integer -> NominalDiffTime)
-> Parser (Map Text Value) (Maybe Integer)
-> Parser (Map Text Value) NominalDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Integer)
forall i.
(Read i, Integral i) =>
Text -> Parser (Map Text Value) (Maybe i)
optInt Text
"db-pool-timeout")
Parser
(Map Text Value)
(Maybe QualifiedIdentifier
-> Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe QualifiedIdentifier)
-> Parser
(Map Text Value)
(Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> QualifiedIdentifier)
-> Maybe Text -> Maybe QualifiedIdentifier
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> QualifiedIdentifier
toQi (Maybe Text -> Maybe QualifiedIdentifier)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe QualifiedIdentifier)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
forall a.
Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
optWithAlias (Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"db-pre-request")
(Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"pre-request"))
Parser
(Map Text Value)
(Bool
-> Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Bool
-> Parser
(Map Text Value)
(Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool)
-> Parser (Map Text Value) (Maybe Bool)
-> Parser (Map Text Value) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Bool)
optBool Text
"db-prepared-statements")
Parser
(Map Text Value)
(Maybe QualifiedIdentifier
-> NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe QualifiedIdentifier)
-> Parser
(Map Text Value)
(NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> QualifiedIdentifier)
-> Maybe Text -> Maybe QualifiedIdentifier
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> QualifiedIdentifier
toQi (Maybe Text -> Maybe QualifiedIdentifier)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe QualifiedIdentifier)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
forall a.
Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
optWithAlias (Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"db-root-spec")
(Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"root-spec"))
Parser
(Map Text Value)
(NonEmpty Text
-> Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (NonEmpty Text)
-> Parser
(Map Text Value)
(Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([Text] -> NonEmpty Text
forall a. [a] -> NonEmpty a
fromList ([Text] -> NonEmpty Text)
-> (Value -> [Text]) -> Value -> NonEmpty Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> [Text]
splitOnCommas (Value -> NonEmpty Text)
-> Parser (Map Text Value) Value
-> Parser (Map Text Value) (NonEmpty Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Map Text Value) (Maybe Value)
-> Parser (Map Text Value) (Maybe Value)
-> FilePath
-> Parser (Map Text Value) Value
forall a.
Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> FilePath
-> Parser (Map Text Value) a
reqWithAlias (Text -> Parser (Map Text Value) (Maybe Value)
optValue Text
"db-schemas")
(Text -> Parser (Map Text Value) (Maybe Value)
optValue Text
"db-schema")
FilePath
"missing key: either db-schemas or db-schema must be set")
Parser
(Map Text Value)
(Bool
-> Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Bool
-> Parser
(Map Text Value)
(Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
True (Maybe Bool -> Bool)
-> Parser (Map Text Value) (Maybe Bool)
-> Parser (Map Text Value) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Bool)
optBool Text
"db-config")
Parser
(Map Text Value)
(Bool
-> Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Bool
-> Parser
(Map Text Value)
(Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ((Bool, Bool) -> Bool) -> Parser (Map Text Value) Bool
parseTxEnd Text
"db-tx-end" (Bool, Bool) -> Bool
forall a b. (a, b) -> b
snd
Parser
(Map Text Value)
(Bool
-> Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Bool
-> Parser
(Map Text Value)
(Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> ((Bool, Bool) -> Bool) -> Parser (Map Text Value) Bool
parseTxEnd Text
"db-tx-end" (Bool, Bool) -> Bool
forall a b. (a, b) -> a
fst
Parser
(Map Text Value)
(Text
-> Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Text
-> Parser
(Map Text Value)
(Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser (Map Text Value) Text
reqString Text
"db-uri"
Parser
(Map Text Value)
(Maybe FilePath
-> Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe FilePath)
-> Parser
(Map Text Value)
(Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe FilePath -> Parser (Map Text Value) (Maybe FilePath)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe FilePath
optPath
Parser
(Map Text Value)
(Maybe JWKSet
-> Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe JWKSet)
-> Parser
(Map Text Value)
(Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe JWKSet -> Parser (Map Text Value) (Maybe JWKSet)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe JWKSet
forall a. Maybe a
Nothing
Parser
(Map Text Value)
(Maybe StringOrURI
-> JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe StringOrURI)
-> Parser
(Map Text Value)
(JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser (Map Text Value) (Maybe StringOrURI)
parseJwtAudience Text
"jwt-aud"
Parser
(Map Text Value)
(JSPath
-> Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) JSPath
-> Parser
(Map Text Value)
(Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> Parser (Map Text Value) JSPath
parseRoleClaimKey Text
"jwt-role-claim-key" Text
"role-claim-key"
Parser
(Map Text Value)
(Maybe ByteString
-> Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe ByteString)
-> Parser
(Map Text Value)
(Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> ByteString) -> Maybe Text -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
encodeUtf8 (Maybe Text -> Maybe ByteString)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe ByteString)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"jwt-secret")
Parser
(Map Text Value)
(Bool
-> LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) Bool
-> Parser
(Map Text Value)
(LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Bool -> Maybe Bool -> Bool
forall a. a -> Maybe a -> a
fromMaybe Bool
False (Maybe Bool -> Bool)
-> Parser (Map Text Value) (Maybe Bool)
-> Parser (Map Text Value) Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Map Text Value) (Maybe Bool)
-> Parser (Map Text Value) (Maybe Bool)
-> Parser (Map Text Value) (Maybe Bool)
forall a.
Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
optWithAlias
(Text -> Parser (Map Text Value) (Maybe Bool)
optBool Text
"jwt-secret-is-base64")
(Text -> Parser (Map Text Value) (Maybe Bool)
optBool Text
"secret-is-base64"))
Parser
(Map Text Value)
(LogLevel
-> OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) LogLevel
-> Parser
(Map Text Value)
(OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser (Map Text Value) LogLevel
parseLogLevel Text
"log-level"
Parser
(Map Text Value)
(OpenAPIMode
-> Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) OpenAPIMode
-> Parser
(Map Text Value)
(Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser (Map Text Value) OpenAPIMode
parseOpenAPIMode Text
"openapi-mode"
Parser
(Map Text Value)
(Maybe Text
-> [ByteString]
-> Text
-> Int
-> Maybe FilePath
-> FileMode
-> AppConfig)
-> Parser (Map Text Value) (Maybe Text)
-> Parser
(Map Text Value)
([ByteString]
-> Text -> Int -> Maybe FilePath -> FileMode -> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser (Map Text Value) (Maybe Text)
parseOpenAPIServerProxyURI Text
"openapi-server-proxy-uri"
Parser
(Map Text Value)
([ByteString]
-> Text -> Int -> Maybe FilePath -> FileMode -> AppConfig)
-> Parser (Map Text Value) [ByteString]
-> Parser
(Map Text Value)
(Text -> Int -> Maybe FilePath -> FileMode -> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ([ByteString]
-> (Value -> [ByteString]) -> Maybe Value -> [ByteString]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] ((Text -> ByteString) -> [Text] -> [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
encodeUtf8 ([Text] -> [ByteString])
-> (Value -> [Text]) -> Value -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> [Text]
splitOnCommas) (Maybe Value -> [ByteString])
-> Parser (Map Text Value) (Maybe Value)
-> Parser (Map Text Value) [ByteString]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Value)
optValue Text
"raw-media-types")
Parser
(Map Text Value)
(Text -> Int -> Maybe FilePath -> FileMode -> AppConfig)
-> Parser (Map Text Value) Text
-> Parser
(Map Text Value) (Int -> Maybe FilePath -> FileMode -> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Text -> Maybe Text -> Text
forall a. a -> Maybe a -> a
fromMaybe Text
"!4" (Maybe Text -> Text)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"server-host")
Parser
(Map Text Value) (Int -> Maybe FilePath -> FileMode -> AppConfig)
-> Parser (Map Text Value) Int
-> Parser
(Map Text Value) (Maybe FilePath -> FileMode -> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Int -> Maybe Int -> Int
forall a. a -> Maybe a -> a
fromMaybe Int
3000 (Maybe Int -> Int)
-> Parser (Map Text Value) (Maybe Int)
-> Parser (Map Text Value) Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Int)
forall i.
(Read i, Integral i) =>
Text -> Parser (Map Text Value) (Maybe i)
optInt Text
"server-port")
Parser (Map Text Value) (Maybe FilePath -> FileMode -> AppConfig)
-> Parser (Map Text Value) (Maybe FilePath)
-> Parser (Map Text Value) (FileMode -> AppConfig)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((Text -> FilePath) -> Maybe Text -> Maybe FilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> FilePath
T.unpack (Maybe Text -> Maybe FilePath)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe FilePath)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Parser (Map Text Value) (Maybe Text)
optString Text
"server-unix-socket")
Parser (Map Text Value) (FileMode -> AppConfig)
-> Parser (Map Text Value) FileMode
-> Parser (Map Text Value) AppConfig
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Parser (Map Text Value) FileMode
parseSocketFileMode Text
"server-unix-socket-mode"
where
parseAppSettings :: C.Key -> C.Parser C.Config [(Text, Text)]
parseAppSettings :: Text -> Parser (Map Text Value) [(Text, Text)]
parseAppSettings Text
key = [(Text, Text)] -> [(Text, Text)]
addFromEnv ([(Text, Text)] -> [(Text, Text)])
-> ([(Text, Value)] -> [(Text, Text)])
-> [(Text, Value)]
-> [(Text, Text)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Text, Value) -> (Text, Text))
-> [(Text, Value)] -> [(Text, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Value -> Text) -> (Text, Value) -> (Text, Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Value -> Text
coerceText) ([(Text, Value)] -> [(Text, Text)])
-> Parser (Map Text Value) [(Text, Value)]
-> Parser (Map Text Value) [(Text, Text)]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text
-> Parser Value Value -> Parser (Map Text Value) [(Text, Value)]
forall a.
Text -> Parser Value a -> Parser (Map Text Value) [(Text, a)]
C.subassocs Text
key Parser Value Value
C.value
where
addFromEnv :: [(Text, Text)] -> [(Text, Text)]
addFromEnv [(Text, Text)]
f = Map Text Text -> [(Text, Text)]
forall k a. Map k a -> [(k, a)]
M.toList (Map Text Text -> [(Text, Text)])
-> Map Text Text -> [(Text, Text)]
forall a b. (a -> b) -> a -> b
$ Map Text Text -> Map Text Text -> Map Text Text
forall k a. Ord k => Map k a -> Map k a -> Map k a
M.union Map Text Text
fromEnv (Map Text Text -> Map Text Text) -> Map Text Text -> Map Text Text
forall a b. (a -> b) -> a -> b
$ [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Text, Text)]
f
fromEnv :: Map Text Text
fromEnv = (Maybe Text -> Text) -> Map (Maybe Text) Text -> Map Text Text
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
M.mapKeys Maybe Text -> Text
forall a. HasCallStack => Maybe a -> a
fromJust (Map (Maybe Text) Text -> Map Text Text)
-> Map (Maybe Text) Text -> Map Text Text
forall a b. (a -> b) -> a -> b
$ (Maybe Text -> Text -> Bool)
-> Map (Maybe Text) Text -> Map (Maybe Text) Text
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
M.filterWithKey (\Maybe Text
k Text
_ -> Maybe Text -> Bool
forall a. Maybe a -> Bool
isJust Maybe Text
k) (Map (Maybe Text) Text -> Map (Maybe Text) Text)
-> Map (Maybe Text) Text -> Map (Maybe Text) Text
forall a b. (a -> b) -> a -> b
$ (FilePath -> Maybe Text) -> Environment -> Map (Maybe Text) Text
forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
M.mapKeys FilePath -> Maybe Text
forall a. StringConv a Text => a -> Maybe Text
normalize Environment
env
normalize :: a -> Maybe Text
normalize a
k = (Text
"app.settings." Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text) -> Maybe Text -> Maybe Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Maybe Text
T.stripPrefix Text
"PGRST_APP_SETTINGS_" (a -> Text
forall a b. StringConv a b => a -> b
toS a
k)
parseSocketFileMode :: C.Key -> C.Parser C.Config FileMode
parseSocketFileMode :: Text -> Parser (Map Text Value) FileMode
parseSocketFileMode Text
k =
Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k Parser (Map Text Value) (Maybe Text)
-> (Maybe Text -> Parser (Map Text Value) FileMode)
-> Parser (Map Text Value) FileMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> FileMode -> Parser (Map Text Value) FileMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure FileMode
432
Just Text
fileModeText ->
case ReadS FileMode
forall a. (Eq a, Num a) => ReadS a
readOct ReadS FileMode -> ReadS FileMode
forall a b. (a -> b) -> a -> b
$ Text -> FilePath
T.unpack Text
fileModeText of
[] ->
FilePath -> Parser (Map Text Value) FileMode
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Invalid server-unix-socket-mode: not an octal"
(FileMode
fileMode, FilePath
_):[(FileMode, FilePath)]
_ ->
if FileMode
fileMode FileMode -> FileMode -> Bool
forall a. Ord a => a -> a -> Bool
< FileMode
384 Bool -> Bool -> Bool
|| FileMode
fileMode FileMode -> FileMode -> Bool
forall a. Ord a => a -> a -> Bool
> FileMode
511
then FilePath -> Parser (Map Text Value) FileMode
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Invalid server-unix-socket-mode: needs to be between 600 and 777"
else FileMode -> Parser (Map Text Value) FileMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure FileMode
fileMode
parseOpenAPIMode :: C.Key -> C.Parser C.Config OpenAPIMode
parseOpenAPIMode :: Text -> Parser (Map Text Value) OpenAPIMode
parseOpenAPIMode Text
k =
Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k Parser (Map Text Value) (Maybe Text)
-> (Maybe Text -> Parser (Map Text Value) OpenAPIMode)
-> Parser (Map Text Value) OpenAPIMode
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> OpenAPIMode -> Parser (Map Text Value) OpenAPIMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure OpenAPIMode
OAFollowPriv
Just Text
"follow-privileges" -> OpenAPIMode -> Parser (Map Text Value) OpenAPIMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure OpenAPIMode
OAFollowPriv
Just Text
"ignore-privileges" -> OpenAPIMode -> Parser (Map Text Value) OpenAPIMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure OpenAPIMode
OAIgnorePriv
Just Text
"disabled" -> OpenAPIMode -> Parser (Map Text Value) OpenAPIMode
forall (f :: * -> *) a. Applicative f => a -> f a
pure OpenAPIMode
OADisabled
Just Text
_ -> FilePath -> Parser (Map Text Value) OpenAPIMode
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Invalid openapi-mode. Check your configuration."
parseOpenAPIServerProxyURI :: C.Key -> C.Parser C.Config (Maybe Text)
parseOpenAPIServerProxyURI :: Text -> Parser (Map Text Value) (Maybe Text)
parseOpenAPIServerProxyURI Text
k =
Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k Parser (Map Text Value) (Maybe Text)
-> (Maybe Text -> Parser (Map Text Value) (Maybe Text))
-> Parser (Map Text Value) (Maybe Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> Maybe Text -> Parser (Map Text Value) (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Text
forall a. Maybe a
Nothing
Just Text
val | Text -> Bool
isMalformedProxyUri Text
val -> FilePath -> Parser (Map Text Value) (Maybe Text)
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Malformed proxy uri, a correct example: https://example.com:8443/basePath"
| Bool
otherwise -> Maybe Text -> Parser (Map Text Value) (Maybe Text)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe Text -> Parser (Map Text Value) (Maybe Text))
-> Maybe Text -> Parser (Map Text Value) (Maybe Text)
forall a b. (a -> b) -> a -> b
$ Text -> Maybe Text
forall a. a -> Maybe a
Just Text
val
parseJwtAudience :: C.Key -> C.Parser C.Config (Maybe StringOrURI)
parseJwtAudience :: Text -> Parser (Map Text Value) (Maybe StringOrURI)
parseJwtAudience Text
k =
Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k Parser (Map Text Value) (Maybe Text)
-> (Maybe Text -> Parser (Map Text Value) (Maybe StringOrURI))
-> Parser (Map Text Value) (Maybe StringOrURI)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> Maybe StringOrURI -> Parser (Map Text Value) (Maybe StringOrURI)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe StringOrURI
forall a. Maybe a
Nothing
Just Text
aud -> case Getting (First StringOrURI) FilePath StringOrURI
-> FilePath -> Maybe StringOrURI
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First StringOrURI) FilePath StringOrURI
forall s. (Cons s s Char Char, AsEmpty s) => Prism' s StringOrURI
stringOrUri (Text -> FilePath
T.unpack Text
aud) of
Maybe StringOrURI
Nothing -> FilePath -> Parser (Map Text Value) (Maybe StringOrURI)
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Invalid Jwt audience. Check your configuration."
Maybe StringOrURI
aud' -> Maybe StringOrURI -> Parser (Map Text Value) (Maybe StringOrURI)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe StringOrURI
aud'
parseLogLevel :: C.Key -> C.Parser C.Config LogLevel
parseLogLevel :: Text -> Parser (Map Text Value) LogLevel
parseLogLevel Text
k =
Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k Parser (Map Text Value) (Maybe Text)
-> (Maybe Text -> Parser (Map Text Value) LogLevel)
-> Parser (Map Text Value) LogLevel
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> LogLevel -> Parser (Map Text Value) LogLevel
forall (f :: * -> *) a. Applicative f => a -> f a
pure LogLevel
LogError
Just Text
"crit" -> LogLevel -> Parser (Map Text Value) LogLevel
forall (f :: * -> *) a. Applicative f => a -> f a
pure LogLevel
LogCrit
Just Text
"error" -> LogLevel -> Parser (Map Text Value) LogLevel
forall (f :: * -> *) a. Applicative f => a -> f a
pure LogLevel
LogError
Just Text
"warn" -> LogLevel -> Parser (Map Text Value) LogLevel
forall (f :: * -> *) a. Applicative f => a -> f a
pure LogLevel
LogWarn
Just Text
"info" -> LogLevel -> Parser (Map Text Value) LogLevel
forall (f :: * -> *) a. Applicative f => a -> f a
pure LogLevel
LogInfo
Just Text
_ -> FilePath -> Parser (Map Text Value) LogLevel
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Invalid logging level. Check your configuration."
parseTxEnd :: C.Key -> ((Bool, Bool) -> Bool) -> C.Parser C.Config Bool
parseTxEnd :: Text -> ((Bool, Bool) -> Bool) -> Parser (Map Text Value) Bool
parseTxEnd Text
k (Bool, Bool) -> Bool
f =
Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k Parser (Map Text Value) (Maybe Text)
-> (Maybe Text -> Parser (Map Text Value) Bool)
-> Parser (Map Text Value) Bool
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> Bool -> Parser (Map Text Value) Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Parser (Map Text Value) Bool)
-> Bool -> Parser (Map Text Value) Bool
forall a b. (a -> b) -> a -> b
$ (Bool, Bool) -> Bool
f (Bool
False, Bool
False)
Just Text
"commit" -> Bool -> Parser (Map Text Value) Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Parser (Map Text Value) Bool)
-> Bool -> Parser (Map Text Value) Bool
forall a b. (a -> b) -> a -> b
$ (Bool, Bool) -> Bool
f (Bool
False, Bool
False)
Just Text
"commit-allow-override" -> Bool -> Parser (Map Text Value) Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Parser (Map Text Value) Bool)
-> Bool -> Parser (Map Text Value) Bool
forall a b. (a -> b) -> a -> b
$ (Bool, Bool) -> Bool
f (Bool
False, Bool
True)
Just Text
"rollback" -> Bool -> Parser (Map Text Value) Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Parser (Map Text Value) Bool)
-> Bool -> Parser (Map Text Value) Bool
forall a b. (a -> b) -> a -> b
$ (Bool, Bool) -> Bool
f (Bool
True, Bool
False)
Just Text
"rollback-allow-override" -> Bool -> Parser (Map Text Value) Bool
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Bool -> Parser (Map Text Value) Bool)
-> Bool -> Parser (Map Text Value) Bool
forall a b. (a -> b) -> a -> b
$ (Bool, Bool) -> Bool
f (Bool
True, Bool
True)
Just Text
_ -> FilePath -> Parser (Map Text Value) Bool
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
"Invalid transaction termination. Check your configuration."
parseRoleClaimKey :: C.Key -> C.Key -> C.Parser C.Config JSPath
parseRoleClaimKey :: Text -> Text -> Parser (Map Text Value) JSPath
parseRoleClaimKey Text
k Text
al =
Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
forall a.
Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
optWithAlias (Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k) (Text -> Parser (Map Text Value) (Maybe Text)
optString Text
al) Parser (Map Text Value) (Maybe Text)
-> (Maybe Text -> Parser (Map Text Value) JSPath)
-> Parser (Map Text Value) JSPath
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Maybe Text
Nothing -> JSPath -> Parser (Map Text Value) JSPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure [Text -> JSPathExp
JSPKey Text
"role"]
Just Text
rck -> (Text -> Parser (Map Text Value) JSPath)
-> (JSPath -> Parser (Map Text Value) JSPath)
-> Either Text JSPath
-> Parser (Map Text Value) JSPath
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (FilePath -> Parser (Map Text Value) JSPath
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (FilePath -> Parser (Map Text Value) JSPath)
-> (Text -> FilePath) -> Text -> Parser (Map Text Value) JSPath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
forall a b. (Show a, ConvertText FilePath b) => a -> b
show) JSPath -> Parser (Map Text Value) JSPath
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either Text JSPath -> Parser (Map Text Value) JSPath)
-> Either Text JSPath -> Parser (Map Text Value) JSPath
forall a b. (a -> b) -> a -> b
$ Text -> Either Text JSPath
pRoleClaimKey Text
rck
reqWithAlias :: C.Parser C.Config (Maybe a) -> C.Parser C.Config (Maybe a) -> [Char] -> C.Parser C.Config a
reqWithAlias :: Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> FilePath
-> Parser (Map Text Value) a
reqWithAlias Parser (Map Text Value) (Maybe a)
orig Parser (Map Text Value) (Maybe a)
alias FilePath
err =
Parser (Map Text Value) (Maybe a)
orig Parser (Map Text Value) (Maybe a)
-> (Maybe a -> Parser (Map Text Value) a)
-> Parser (Map Text Value) a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just a
v -> a -> Parser (Map Text Value) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
v
Maybe a
Nothing ->
Parser (Map Text Value) (Maybe a)
alias Parser (Map Text Value) (Maybe a)
-> (Maybe a -> Parser (Map Text Value) a)
-> Parser (Map Text Value) a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just a
v -> a -> Parser (Map Text Value) a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
v
Maybe a
Nothing -> FilePath -> Parser (Map Text Value) a
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail FilePath
err
optWithAlias :: C.Parser C.Config (Maybe a) -> C.Parser C.Config (Maybe a) -> C.Parser C.Config (Maybe a)
optWithAlias :: Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
-> Parser (Map Text Value) (Maybe a)
optWithAlias Parser (Map Text Value) (Maybe a)
orig Parser (Map Text Value) (Maybe a)
alias =
Parser (Map Text Value) (Maybe a)
orig Parser (Map Text Value) (Maybe a)
-> (Maybe a -> Parser (Map Text Value) (Maybe a))
-> Parser (Map Text Value) (Maybe a)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Just a
v -> Maybe a -> Parser (Map Text Value) (Maybe a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe a -> Parser (Map Text Value) (Maybe a))
-> Maybe a -> Parser (Map Text Value) (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
v
Maybe a
Nothing -> Parser (Map Text Value) (Maybe a)
alias
reqString :: C.Key -> C.Parser C.Config Text
reqString :: Text -> Parser (Map Text Value) Text
reqString Text
k = (Text -> Parser Value Text -> Parser (Map Text Value) Text)
-> Text -> (Value -> Text) -> Parser (Map Text Value) Text
forall a b.
JustIfMaybe a b =>
(Text -> Parser Value a -> Parser (Map Text Value) b)
-> Text -> (Value -> a) -> Parser (Map Text Value) b
overrideFromDbOrEnvironment Text -> Parser Value Text -> Parser (Map Text Value) Text
forall a. Text -> Parser Value a -> Parser (Map Text Value) a
C.required Text
k Value -> Text
coerceText
optString :: C.Key -> C.Parser C.Config (Maybe Text)
optString :: Text -> Parser (Map Text Value) (Maybe Text)
optString Text
k = (Text -> Bool) -> Maybe Text -> Maybe Text
forall (m :: * -> *) a. MonadPlus m => (a -> Bool) -> m a -> m a
mfilter (Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
/= Text
"") (Maybe Text -> Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
-> Parser (Map Text Value) (Maybe Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text -> Parser Value Text -> Parser (Map Text Value) (Maybe Text))
-> Text -> (Value -> Text) -> Parser (Map Text Value) (Maybe Text)
forall a b.
JustIfMaybe a b =>
(Text -> Parser Value a -> Parser (Map Text Value) b)
-> Text -> (Value -> a) -> Parser (Map Text Value) b
overrideFromDbOrEnvironment Text -> Parser Value Text -> Parser (Map Text Value) (Maybe Text)
forall a.
Text -> Parser Value a -> Parser (Map Text Value) (Maybe a)
C.optional Text
k Value -> Text
coerceText
optValue :: C.Key -> C.Parser C.Config (Maybe C.Value)
optValue :: Text -> Parser (Map Text Value) (Maybe Value)
optValue Text
k = (Text
-> Parser Value Value -> Parser (Map Text Value) (Maybe Value))
-> Text
-> (Value -> Value)
-> Parser (Map Text Value) (Maybe Value)
forall a b.
JustIfMaybe a b =>
(Text -> Parser Value a -> Parser (Map Text Value) b)
-> Text -> (Value -> a) -> Parser (Map Text Value) b
overrideFromDbOrEnvironment Text -> Parser Value Value -> Parser (Map Text Value) (Maybe Value)
forall a.
Text -> Parser Value a -> Parser (Map Text Value) (Maybe a)
C.optional Text
k Value -> Value
forall a. a -> a
identity
optInt :: (Read i, Integral i) => C.Key -> C.Parser C.Config (Maybe i)
optInt :: Text -> Parser (Map Text Value) (Maybe i)
optInt Text
k = Maybe (Maybe i) -> Maybe i
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Maybe (Maybe i) -> Maybe i)
-> Parser (Map Text Value) (Maybe (Maybe i))
-> Parser (Map Text Value) (Maybe i)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text
-> Parser Value (Maybe i)
-> Parser (Map Text Value) (Maybe (Maybe i)))
-> Text
-> (Value -> Maybe i)
-> Parser (Map Text Value) (Maybe (Maybe i))
forall a b.
JustIfMaybe a b =>
(Text -> Parser Value a -> Parser (Map Text Value) b)
-> Text -> (Value -> a) -> Parser (Map Text Value) b
overrideFromDbOrEnvironment Text
-> Parser Value (Maybe i)
-> Parser (Map Text Value) (Maybe (Maybe i))
forall a.
Text -> Parser Value a -> Parser (Map Text Value) (Maybe a)
C.optional Text
k Value -> Maybe i
forall i. (Read i, Integral i) => Value -> Maybe i
coerceInt
optBool :: C.Key -> C.Parser C.Config (Maybe Bool)
optBool :: Text -> Parser (Map Text Value) (Maybe Bool)
optBool Text
k = Maybe (Maybe Bool) -> Maybe Bool
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (Maybe (Maybe Bool) -> Maybe Bool)
-> Parser (Map Text Value) (Maybe (Maybe Bool))
-> Parser (Map Text Value) (Maybe Bool)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Text
-> Parser Value (Maybe Bool)
-> Parser (Map Text Value) (Maybe (Maybe Bool)))
-> Text
-> (Value -> Maybe Bool)
-> Parser (Map Text Value) (Maybe (Maybe Bool))
forall a b.
JustIfMaybe a b =>
(Text -> Parser Value a -> Parser (Map Text Value) b)
-> Text -> (Value -> a) -> Parser (Map Text Value) b
overrideFromDbOrEnvironment Text
-> Parser Value (Maybe Bool)
-> Parser (Map Text Value) (Maybe (Maybe Bool))
forall a.
Text -> Parser Value a -> Parser (Map Text Value) (Maybe a)
C.optional Text
k Value -> Maybe Bool
coerceBool
overrideFromDbOrEnvironment :: JustIfMaybe a b =>
(C.Key -> C.Parser C.Value a -> C.Parser C.Config b) ->
C.Key -> (C.Value -> a) -> C.Parser C.Config b
overrideFromDbOrEnvironment :: (Text -> Parser Value a -> Parser (Map Text Value) b)
-> Text -> (Value -> a) -> Parser (Map Text Value) b
overrideFromDbOrEnvironment Text -> Parser Value a -> Parser (Map Text Value) b
necessity Text
key Value -> a
coercion =
case Maybe Text
reloadableDbSetting Maybe Text -> Maybe Text -> Maybe Text
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> FilePath -> Environment -> Maybe Text
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup FilePath
envVarName Environment
env of
Just Text
dbOrEnvVal -> b -> Parser (Map Text Value) b
forall (f :: * -> *) a. Applicative f => a -> f a
pure (b -> Parser (Map Text Value) b) -> b -> Parser (Map Text Value) b
forall a b. (a -> b) -> a -> b
$ a -> b
forall a b. JustIfMaybe a b => a -> b
justIfMaybe (a -> b) -> a -> b
forall a b. (a -> b) -> a -> b
$ Value -> a
coercion (Value -> a) -> Value -> a
forall a b. (a -> b) -> a -> b
$ Text -> Value
C.String Text
dbOrEnvVal
Maybe Text
Nothing -> Text -> Parser Value a -> Parser (Map Text Value) b
necessity Text
key (Value -> a
coercion (Value -> a) -> Parser Value Value -> Parser Value a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Value Value
C.value)
where
dashToUnderscore :: Char -> Char
dashToUnderscore Char
'-' = Char
'_'
dashToUnderscore Char
c = Char
c
envVarName :: FilePath
envVarName = FilePath
"PGRST_" FilePath -> ShowS
forall a. Semigroup a => a -> a -> a
<> (Char -> Char
toUpper (Char -> Char) -> (Char -> Char) -> Char -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> Char
dashToUnderscore (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> FilePath
forall a b. StringConv a b => a -> b
toS Text
key)
reloadableDbSetting :: Maybe Text
reloadableDbSetting =
let dbSettingName :: Text
dbSettingName = FilePath -> Text
T.pack (FilePath -> Text) -> FilePath -> Text
forall a b. (a -> b) -> a -> b
$ Char -> Char
dashToUnderscore (Char -> Char) -> ShowS
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> FilePath
forall a b. StringConv a b => a -> b
toS Text
key in
if Text
dbSettingName Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [
Text
"server_host", Text
"server_port", Text
"server_unix_socket", Text
"server_unix_socket_mode", Text
"log_level",
Text
"db_anon_role", Text
"db_uri", Text
"db_channel_enabled", Text
"db_channel", Text
"db_pool", Text
"db_pool_timeout", Text
"db_config"]
then Text -> [(Text, Text)] -> Maybe Text
forall a b. Eq a => a -> [(a, b)] -> Maybe b
lookup Text
dbSettingName [(Text, Text)]
dbSettings
else Maybe Text
forall a. Maybe a
Nothing
coerceText :: C.Value -> Text
coerceText :: Value -> Text
coerceText (C.String Text
s) = Text
s
coerceText Value
v = Value -> Text
forall a b. (Show a, ConvertText FilePath b) => a -> b
show Value
v
coerceInt :: (Read i, Integral i) => C.Value -> Maybe i
coerceInt :: Value -> Maybe i
coerceInt (C.Number Scientific
x) = Either Double i -> Maybe i
forall l r. Either l r -> Maybe r
rightToMaybe (Either Double i -> Maybe i) -> Either Double i -> Maybe i
forall a b. (a -> b) -> a -> b
$ Scientific -> Either Double i
forall r i. (RealFloat r, Integral i) => Scientific -> Either r i
floatingOrInteger Scientific
x
coerceInt (C.String Text
x) = FilePath -> Maybe i
forall a. Read a => FilePath -> Maybe a
readMaybe (FilePath -> Maybe i) -> FilePath -> Maybe i
forall a b. (a -> b) -> a -> b
$ Text -> FilePath
forall a b. StringConv a b => a -> b
toS Text
x
coerceInt Value
_ = Maybe i
forall a. Maybe a
Nothing
coerceBool :: C.Value -> Maybe Bool
coerceBool :: Value -> Maybe Bool
coerceBool (C.Bool Bool
b) = Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
b
coerceBool (C.String Text
s) =
case FilePath -> Maybe Bool
forall a. Read a => FilePath -> Maybe a
readMaybe (FilePath -> Maybe Bool)
-> (Text -> FilePath) -> Text -> Maybe Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> FilePath
forall a b. StringConv a b => a -> b
toS (Text -> Maybe Bool) -> Text -> Maybe Bool
forall a b. (a -> b) -> a -> b
$ Text -> Text
T.toTitle (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.filter Char -> Bool
isAlpha (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ Text -> Text
forall a b. StringConv a b => a -> b
toS Text
s of
Just Bool
b -> Bool -> Maybe Bool
forall a. a -> Maybe a
Just Bool
b
Maybe Bool
Nothing -> (Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0) (Integer -> Bool) -> Maybe Integer -> Maybe Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (FilePath -> Maybe Integer
forall a. Read a => FilePath -> Maybe a
readMaybe (FilePath -> Maybe Integer) -> FilePath -> Maybe Integer
forall a b. (a -> b) -> a -> b
$ Text -> FilePath
forall a b. StringConv a b => a -> b
toS Text
s :: Maybe Integer)
coerceBool Value
_ = Maybe Bool
forall a. Maybe a
Nothing
splitOnCommas :: C.Value -> [Text]
splitOnCommas :: Value -> [Text]
splitOnCommas (C.String Text
s) = Text -> Text
T.strip (Text -> Text) -> [Text] -> [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> [Text]
T.splitOn Text
"," Text
s
splitOnCommas Value
_ = []
readSecretFile :: AppConfig -> IO AppConfig
readSecretFile :: AppConfig -> IO AppConfig
readSecretFile AppConfig
conf =
IO AppConfig
-> (Text -> IO AppConfig) -> Maybe Text -> IO AppConfig
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (AppConfig -> IO AppConfig
forall (m :: * -> *) a. Monad m => a -> m a
return AppConfig
conf) Text -> IO AppConfig
forall a. StringConv a FilePath => a -> IO AppConfig
readSecret Maybe Text
maybeFilename
where
maybeFilename :: Maybe Text
maybeFilename = Text -> Text -> Maybe Text
T.stripPrefix Text
"@" (Text -> Maybe Text)
-> (ByteString -> Text) -> ByteString -> Maybe Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeUtf8 (ByteString -> Maybe Text) -> Maybe ByteString -> Maybe Text
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< AppConfig -> Maybe ByteString
configJwtSecret AppConfig
conf
readSecret :: a -> IO AppConfig
readSecret a
filename = do
ByteString
jwtSecret <- ByteString -> ByteString
chomp (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO ByteString
BS.readFile (a -> FilePath
forall a b. StringConv a b => a -> b
toS a
filename)
AppConfig -> IO AppConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (AppConfig -> IO AppConfig) -> AppConfig -> IO AppConfig
forall a b. (a -> b) -> a -> b
$ AppConfig
conf { configJwtSecret :: Maybe ByteString
configJwtSecret = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
jwtSecret }
chomp :: ByteString -> ByteString
chomp ByteString
bs = ByteString -> Maybe ByteString -> ByteString
forall a. a -> Maybe a -> a
fromMaybe ByteString
bs (ByteString -> ByteString -> Maybe ByteString
BS.stripSuffix ByteString
"\n" ByteString
bs)
decodeSecret :: AppConfig -> IO AppConfig
decodeSecret :: AppConfig -> IO AppConfig
decodeSecret conf :: AppConfig
conf@AppConfig{Bool
Int
[(Text, Text)]
[ByteString]
[Text]
JSPath
Maybe Integer
Maybe FilePath
Maybe ByteString
Maybe Text
Maybe StringOrURI
Maybe JWKSet
Maybe QualifiedIdentifier
Text
FileMode
NonEmpty Text
NominalDiffTime
OpenAPIMode
LogLevel
configServerUnixSocketMode :: FileMode
configServerUnixSocket :: Maybe FilePath
configServerPort :: Int
configServerHost :: Text
configRawMediaTypes :: [ByteString]
configOpenApiServerProxyUri :: Maybe Text
configOpenApiMode :: OpenAPIMode
configLogLevel :: LogLevel
configJwtSecretIsBase64 :: Bool
configJwtSecret :: Maybe ByteString
configJwtRoleClaimKey :: JSPath
configJwtAudience :: Maybe StringOrURI
configJWKS :: Maybe JWKSet
configFilePath :: Maybe FilePath
configDbUri :: Text
configDbTxRollbackAll :: Bool
configDbTxAllowOverride :: Bool
configDbConfig :: Bool
configDbSchemas :: NonEmpty Text
configDbRootSpec :: Maybe QualifiedIdentifier
configDbPreparedStatements :: Bool
configDbPreRequest :: Maybe QualifiedIdentifier
configDbPoolTimeout :: NominalDiffTime
configDbPoolSize :: Int
configDbMaxRows :: Maybe Integer
configDbExtraSearchPath :: [Text]
configDbChannelEnabled :: Bool
configDbChannel :: Text
configDbAnonRole :: Text
configAppSettings :: [(Text, Text)]
configServerUnixSocketMode :: AppConfig -> FileMode
configServerUnixSocket :: AppConfig -> Maybe FilePath
configServerPort :: AppConfig -> Int
configServerHost :: AppConfig -> Text
configRawMediaTypes :: AppConfig -> [ByteString]
configOpenApiServerProxyUri :: AppConfig -> Maybe Text
configOpenApiMode :: AppConfig -> OpenAPIMode
configLogLevel :: AppConfig -> LogLevel
configJwtSecretIsBase64 :: AppConfig -> Bool
configJwtSecret :: AppConfig -> Maybe ByteString
configJwtRoleClaimKey :: AppConfig -> JSPath
configJwtAudience :: AppConfig -> Maybe StringOrURI
configJWKS :: AppConfig -> Maybe JWKSet
configFilePath :: AppConfig -> Maybe FilePath
configDbUri :: AppConfig -> Text
configDbTxRollbackAll :: AppConfig -> Bool
configDbTxAllowOverride :: AppConfig -> Bool
configDbConfig :: AppConfig -> Bool
configDbSchemas :: AppConfig -> NonEmpty Text
configDbRootSpec :: AppConfig -> Maybe QualifiedIdentifier
configDbPreparedStatements :: AppConfig -> Bool
configDbPreRequest :: AppConfig -> Maybe QualifiedIdentifier
configDbPoolTimeout :: AppConfig -> NominalDiffTime
configDbPoolSize :: AppConfig -> Int
configDbMaxRows :: AppConfig -> Maybe Integer
configDbExtraSearchPath :: AppConfig -> [Text]
configDbChannelEnabled :: AppConfig -> Bool
configDbChannel :: AppConfig -> Text
configDbAnonRole :: AppConfig -> Text
configAppSettings :: AppConfig -> [(Text, Text)]
..} =
case (Bool
configJwtSecretIsBase64, Maybe ByteString
configJwtSecret) of
(Bool
True, Just ByteString
secret) ->
(FilePath -> IO AppConfig)
-> (ByteString -> IO AppConfig)
-> Either FilePath ByteString
-> IO AppConfig
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either FilePath -> IO AppConfig
forall (m :: * -> *) a. MonadFail m => FilePath -> m a
fail (AppConfig -> IO AppConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (AppConfig -> IO AppConfig)
-> (ByteString -> AppConfig) -> ByteString -> IO AppConfig
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> AppConfig
updateSecret) (Either FilePath ByteString -> IO AppConfig)
-> Either FilePath ByteString -> IO AppConfig
forall a b. (a -> b) -> a -> b
$ ByteString -> Either FilePath ByteString
decodeB64 ByteString
secret
(Bool, Maybe ByteString)
_ -> AppConfig -> IO AppConfig
forall (m :: * -> *) a. Monad m => a -> m a
return AppConfig
conf
where
updateSecret :: ByteString -> AppConfig
updateSecret ByteString
bs = AppConfig
conf { configJwtSecret :: Maybe ByteString
configJwtSecret = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
bs }
decodeB64 :: ByteString -> Either FilePath ByteString
decodeB64 = ByteString -> Either FilePath ByteString
B64.decode (ByteString -> Either FilePath ByteString)
-> (ByteString -> ByteString)
-> ByteString
-> Either FilePath ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> ByteString
encodeUtf8 (Text -> ByteString)
-> (ByteString -> Text) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
T.strip (Text -> Text) -> (ByteString -> Text) -> ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
replaceUrlChars (Text -> Text) -> (ByteString -> Text) -> ByteString -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Text
decodeUtf8
replaceUrlChars :: Text -> Text
replaceUrlChars = Text -> Text -> Text -> Text
T.replace Text
"_" Text
"/" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
T.replace Text
"-" Text
"+" (Text -> Text) -> (Text -> Text) -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text -> Text -> Text
T.replace Text
"." Text
"="
decodeJWKS :: AppConfig -> AppConfig
decodeJWKS :: AppConfig -> AppConfig
decodeJWKS AppConfig
conf =
AppConfig
conf { configJWKS :: Maybe JWKSet
configJWKS = ByteString -> JWKSet
parseSecret (ByteString -> JWKSet) -> Maybe ByteString -> Maybe JWKSet
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> AppConfig -> Maybe ByteString
configJwtSecret AppConfig
conf }
parseSecret :: ByteString -> JWKSet
parseSecret :: ByteString -> JWKSet
parseSecret ByteString
bytes =
JWKSet -> Maybe JWKSet -> JWKSet
forall a. a -> Maybe a -> a
fromMaybe (JWKSet -> (JWK -> JWKSet) -> Maybe JWK -> JWKSet
forall b a. b -> (a -> b) -> Maybe a -> b
maybe JWKSet
secret (\JWK
jwk' -> [JWK] -> JWKSet
JWT.JWKSet [JWK
jwk']) Maybe JWK
maybeJWK)
Maybe JWKSet
maybeJWKSet
where
maybeJWKSet :: Maybe JWKSet
maybeJWKSet = ByteString -> Maybe JWKSet
forall a. FromJSON a => ByteString -> Maybe a
JSON.decode (ByteString -> ByteString
forall a b. StringConv a b => a -> b
toS ByteString
bytes) :: Maybe JWKSet
maybeJWK :: Maybe JWK
maybeJWK = ByteString -> Maybe JWK
forall a. FromJSON a => ByteString -> Maybe a
JSON.decode (ByteString -> ByteString
forall a b. StringConv a b => a -> b
toS ByteString
bytes) :: Maybe JWK
secret :: JWKSet
secret = [JWK] -> JWKSet
JWT.JWKSet [KeyMaterial -> JWK
JWT.fromKeyMaterial KeyMaterial
keyMaterial]
keyMaterial :: KeyMaterial
keyMaterial = OctKeyParameters -> KeyMaterial
JWT.OctKeyMaterial (OctKeyParameters -> KeyMaterial)
-> (Base64Octets -> OctKeyParameters)
-> Base64Octets
-> KeyMaterial
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Base64Octets -> OctKeyParameters
JWT.OctKeyParameters (Base64Octets -> KeyMaterial) -> Base64Octets -> KeyMaterial
forall a b. (a -> b) -> a -> b
$ ByteString -> Base64Octets
JOSE.Base64Octets ByteString
bytes
readDbUriFile :: Maybe Text -> AppConfig -> IO AppConfig
readDbUriFile :: Maybe Text -> AppConfig -> IO AppConfig
readDbUriFile Maybe Text
maybeDbUri AppConfig
conf =
case Maybe Text
maybeDbUri of
Just Text
prevDbUri ->
AppConfig -> IO AppConfig
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AppConfig -> IO AppConfig) -> AppConfig -> IO AppConfig
forall a b. (a -> b) -> a -> b
$ AppConfig
conf { configDbUri :: Text
configDbUri = Text
prevDbUri }
Maybe Text
Nothing ->
case Text -> Text -> Maybe Text
T.stripPrefix Text
"@" (Text -> Maybe Text) -> Text -> Maybe Text
forall a b. (a -> b) -> a -> b
$ AppConfig -> Text
configDbUri AppConfig
conf of
Maybe Text
Nothing -> AppConfig -> IO AppConfig
forall (m :: * -> *) a. Monad m => a -> m a
return AppConfig
conf
Just Text
filename -> do
Text
dbUri <- Text -> Text
T.strip (Text -> Text) -> IO Text -> IO Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FilePath -> IO Text
readFile (Text -> FilePath
forall a b. StringConv a b => a -> b
toS Text
filename)
AppConfig -> IO AppConfig
forall (m :: * -> *) a. Monad m => a -> m a
return (AppConfig -> IO AppConfig) -> AppConfig -> IO AppConfig
forall a b. (a -> b) -> a -> b
$ AppConfig
conf { configDbUri :: Text
configDbUri = Text
dbUri }
type Environment = M.Map [Char] Text
readPGRSTEnvironment :: IO Environment
readPGRSTEnvironment :: IO Environment
readPGRSTEnvironment =
(FilePath -> Text) -> Map FilePath FilePath -> Environment
forall a b k. (a -> b) -> Map k a -> Map k b
M.map FilePath -> Text
T.pack (Map FilePath FilePath -> Environment)
-> ([(FilePath, FilePath)] -> Map FilePath FilePath)
-> [(FilePath, FilePath)]
-> Environment
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(FilePath, FilePath)] -> Map FilePath FilePath
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList ([(FilePath, FilePath)] -> Map FilePath FilePath)
-> ([(FilePath, FilePath)] -> [(FilePath, FilePath)])
-> [(FilePath, FilePath)]
-> Map FilePath FilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((FilePath, FilePath) -> Bool)
-> [(FilePath, FilePath)] -> [(FilePath, FilePath)]
forall a. (a -> Bool) -> [a] -> [a]
filter (FilePath -> FilePath -> Bool
forall a. Eq a => [a] -> [a] -> Bool
isPrefixOf FilePath
"PGRST_" (FilePath -> Bool)
-> ((FilePath, FilePath) -> FilePath)
-> (FilePath, FilePath)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (FilePath, FilePath) -> FilePath
forall a b. (a, b) -> a
fst) ([(FilePath, FilePath)] -> Environment)
-> IO [(FilePath, FilePath)] -> IO Environment
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO [(FilePath, FilePath)]
getEnvironment