Skip to content

Commit

Permalink
Require JWT secret, remove default, optionally read from file
Browse files Browse the repository at this point in the history
Fixes #474, fixes #495 when file is used
  • Loading branch information
begriffs committed Sep 4, 2016
1 parent 6d5381e commit 8eca2e4
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 17 deletions.
14 changes: 10 additions & 4 deletions main/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ import PostgREST.OpenAPI (isMalformedProxyUri)
import PostgREST.DbStructure

import Data.String (IsString (..))
import Data.Text (stripPrefix)
import Data.Function (id)
import qualified Hasql.Query as H
import qualified Hasql.Session as H
Expand All @@ -21,7 +22,6 @@ import qualified Hasql.Pool as P
import Network.Wai.Handler.Warp
import System.IO (BufferMode (..),
hSetBuffering)
import Web.JWT (secret)
import Data.IORef
#ifndef mingw32_HOST_OS
import System.Posix.Signals
Expand All @@ -42,7 +42,7 @@ main = do
hSetBuffering stdin LineBuffering
hSetBuffering stderr NoBuffering

conf <- readOptions
conf <- loadSecretFile =<< readOptions
let host = configHost conf
port = configPort conf
proxy = configProxyUri conf
Expand All @@ -55,8 +55,6 @@ main = do
when (isMalformedProxyUri $ toS <$> proxy) $ panic
"Malformed proxy uri, a correct example: https://example.com:8443/basePath"

unless (secret "secret" /= configJwtSecret conf) $
putStrLn ("WARNING, running in insecure mode, JWT secret is the default value" :: Text)
putStrLn $ ("Listening on port " :: Text) <> show (configPort conf)

pool <- P.acquire (configPool conf, 10, pgSettings)
Expand Down Expand Up @@ -86,3 +84,11 @@ main = do
#endif

runSettings appSettings $ postgrest conf refDbStructure pool

loadSecretFile :: AppConfig -> IO AppConfig
loadSecretFile conf = do
let s = configJwtSecret conf
real <- case stripPrefix "@" s of
Nothing -> return s -- the string is the secret, not a filename
Just filename -> readFile (toS filename)
return conf { configJwtSecret = real }
9 changes: 5 additions & 4 deletions src/PostgREST/App.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,12 +25,13 @@ import qualified Text.InterpolatedString.Perl6 as P6 (q)

import Network.HTTP.Types.Header
import Network.HTTP.Types.Status
import Network.HTTP.Types.URI (renderSimpleQuery)
import Network.HTTP.Types.URI (renderSimpleQuery)
import Network.Wai
import Network.Wai.Middleware.RequestLogger (logStdout)
import Web.JWT (secret)

import Data.Aeson
import Data.Aeson.Types (emptyArray)
import Data.Aeson.Types (emptyArray)
import Data.Time.Clock.POSIX (getPOSIXTime)
import qualified Data.Vector as V
import qualified Hasql.Transaction as H
Expand Down Expand Up @@ -79,7 +80,7 @@ postgrest conf refDbStructure pool =

let schema = toS $ configSchema conf
apiRequest = userApiRequest schema req body
eClaims = jwtClaims (configJwtSecret conf) (iJWT apiRequest) time
eClaims = jwtClaims (secret $ configJwtSecret conf) (iJWT apiRequest) time
authed = containsRole eClaims
handleReq = runWithClaims conf eClaims (app dbStructure conf) apiRequest
txMode = transactionMode $ iAction apiRequest
Expand Down Expand Up @@ -202,7 +203,7 @@ app dbStructure conf apiRequest =
Just (PayloadJSON (UniformObjects payload))) -> do
let p = V.head payload
singular = iPreferSingular apiRequest
jwtSecret = configJwtSecret conf
jwtSecret = secret $ configJwtSecret conf
returnType = lookup (qiName qi) $ dbProcs dbStructure
returnsJWT = fromMaybe False $ isInfixOf "jwt_claims" <$> returnType
serves [CTApplicationJSON] (iAccepts apiRequest) $ \_ -> case readSqlParts of
Expand Down
6 changes: 2 additions & 4 deletions src/PostgREST/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,6 @@ import Options.Applicative
import Paths_postgrest (version)
import Protolude hiding (intercalate)
import Safe (readMay)
import Web.JWT (Secret, secret)

-- | Data type to store all command line options
data AppConfig = AppConfig {
Expand All @@ -41,7 +40,7 @@ data AppConfig = AppConfig {
, configSchema :: Text
, configHost :: Text
, configPort :: Int
, configJwtSecret :: Secret
, configJwtSecret :: Text
, configPool :: Int
, configMaxRows :: Maybe Integer
, configQuiet :: Bool
Expand All @@ -55,8 +54,7 @@ argParser = AppConfig
<*> (toS <$> strOption (long "schema" <> short 's' <> help "schema to use for API routes" <> metavar "NAME" <> value "public" <> showDefault))
<*> (toS <$> strOption (long "host" <> short 'l' <> help "hostname or ip on which to run HTTP server" <> metavar "HOST" <> value "*4" <> showDefault))
<*> option auto (long "port" <> short 'p' <> help "port number on which to run HTTP server" <> metavar "PORT" <> value 3000 <> showDefault)
<*> (secret . toS <$>
strOption (long "jwt-secret" <> short 'j' <> help "secret used to encrypt and decrypt JWT tokens" <> metavar "SECRET" <> value "secret" <> showDefault))
<*> (toS <$> strOption (long "jwt-secret" <> short 'j' <> help "secret used to encrypt and decrypt JWT tokens" <> metavar "SECRET"))
<*> option auto (long "pool" <> short 'o' <> help "max connections in database pool" <> metavar "COUNT" <> value 10 <> showDefault)
<*> (readMay <$> strOption (long "max-rows" <> short 'm' <> help "max rows in response" <> metavar "COUNT" <> value "infinity" <> showDefault))
<*> pure False
Expand Down
9 changes: 4 additions & 5 deletions test/SpecHelper.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,6 @@ import Data.CaseInsensitive (CI(..))
import Text.Regex.TDFA ((=~))
import qualified Data.ByteString.Char8 as BS
import System.Process (readProcess)
import Web.JWT (secret)

import PostgREST.Config (AppConfig(..))

Expand Down Expand Up @@ -52,19 +51,19 @@ testDbConn = "postgres://postgrest_test_authenticator@localhost:5432/postgrest_t

testCfg :: AppConfig
testCfg =
AppConfig testDbConn "postgrest_test_anonymous" Nothing "test" "localhost" 3000 (secret "safe") 10 Nothing True
AppConfig testDbConn "postgrest_test_anonymous" Nothing "test" "localhost" 3000 "safe" 10 Nothing True

testUnicodeCfg :: AppConfig
testUnicodeCfg =
AppConfig testDbConn "postgrest_test_anonymous" Nothing "تست" "localhost" 3000 (secret "safe") 10 Nothing True
AppConfig testDbConn "postgrest_test_anonymous" Nothing "تست" "localhost" 3000 "safe" 10 Nothing True

testLtdRowsCfg :: AppConfig
testLtdRowsCfg =
AppConfig testDbConn "postgrest_test_anonymous" Nothing "test" "localhost" 3000 (secret "safe") 10 (Just 2) True
AppConfig testDbConn "postgrest_test_anonymous" Nothing "test" "localhost" 3000 "safe" 10 (Just 2) True

testProxyCfg :: AppConfig
testProxyCfg =
AppConfig testDbConn "postgrest_test_anonymous" (Just "https://postgrest.com/openapi.json") "test" "localhost" 3000 (secret "safe") 10 Nothing True
AppConfig testDbConn "postgrest_test_anonymous" (Just "https://postgrest.com/openapi.json") "test" "localhost" 3000 "safe" 10 Nothing True

setupDb :: IO ()
setupDb = do
Expand Down

0 comments on commit 8eca2e4

Please sign in to comment.