graphql-engine/server/src-exec/Main.hs

254 lines
9.7 KiB
Haskell
Raw Normal View History

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
2018-06-27 16:11:32 +03:00
module Main where
import Ops
2018-09-05 14:26:46 +03:00
import Control.Monad.STM (atomically)
2018-06-27 16:11:32 +03:00
import Data.Time.Clock (getCurrentTime)
import Options.Applicative
import System.Environment (lookupEnv)
2018-06-27 16:11:32 +03:00
import System.Exit (exitFailure)
import qualified Control.Concurrent as C
2018-06-27 16:11:32 +03:00
import qualified Data.Aeson as A
import qualified Data.ByteString.Char8 as BC
import qualified Data.ByteString.Lazy as BL
import qualified Data.ByteString.Lazy.Char8 as BLC
import qualified Data.Text as T
import qualified Data.Yaml as Y
import qualified Network.HTTP.Client as HTTP
import qualified Network.HTTP.Client.TLS as HTTP
import qualified Network.Wai.Handler.Warp as Warp
2018-06-27 16:11:32 +03:00
2018-09-05 14:26:46 +03:00
import Hasura.Events.Lib
import Hasura.Logging (defaultLoggerSettings, mkLoggerCtx)
2018-06-27 16:11:32 +03:00
import Hasura.Prelude
import Hasura.RQL.DDL.Metadata (fetchMetadata)
import Hasura.RQL.Types (RoleName (..))
import Hasura.Server.App (mkWaiApp)
import Hasura.Server.Auth
import Hasura.Server.CheckUpdates (checkForUpdates)
2018-06-27 16:11:32 +03:00
import Hasura.Server.Init
import qualified Database.PG.Query as Q
2018-09-05 14:26:46 +03:00
import qualified Network.HTTP.Client.TLS as TLS
import qualified Network.Wreq.Session as WrqS
2018-06-27 16:11:32 +03:00
data RavenOptions
= RavenOptions
{ roConnInfo :: !RawConnInfo
, roMode :: !RavenMode
} deriving (Show, Eq)
data ServeOptions
= ServeOptions
{ soPort :: !(Maybe Int)
, soConnParams :: !Q.ConnParams
, soTxIso :: !Q.TxIsolation
, soRootDir :: !(Maybe String)
, soAccessKey :: !(Maybe AccessKey)
, soAuthHook :: !AuthHookConf
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
, soJwtSecret :: !(Maybe Text)
, soUnAuthRole :: !(Maybe RoleName)
, soCorsConfig :: !CorsConfigFlags
, soEnableConsole :: !Bool
2018-06-27 16:11:32 +03:00
} deriving (Show, Eq)
data RavenMode
= ROServe !ServeOptions
| ROExport
| ROClean
| ROExecute
deriving (Show, Eq)
parseRavenMode :: Parser RavenMode
parseRavenMode = subparser
( command "serve" (info (helper <*> serveOptsParser)
( progDesc "Start the HTTP api server" ))
<> command "export" (info (pure ROExport)
( progDesc "Export graphql-engine's schema to stdout" ))
2018-06-27 16:11:32 +03:00
<> command "clean" (info (pure ROClean)
( progDesc "Clean graphql-engine's metadata to start afresh" ))
2018-06-27 16:11:32 +03:00
<> command "execute" (info (pure ROExecute)
( progDesc "Execute a query" ))
)
where
serveOptsParser = ROServe <$> serveOpts
serveOpts = ServeOptions
<$> parseServerPort
<*> parseConnParams
<*> parseTxIsolation
<*> parseRootDir
<*> parseAccessKey
<*> parseWebHook
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
<*> parseJwtSecret
<*> parseUnAuthRole
<*> parseCorsConfig
<*> parseEnableConsole
2018-06-27 16:11:32 +03:00
parseArgs :: IO RavenOptions
parseArgs = execParser opts
where
optParser = RavenOptions <$> parseRawConnInfo <*> parseRavenMode
opts = info (helper <*> optParser)
( fullDesc <>
header "Hasura's graphql-engine - Exposes Postgres over GraphQL")
2018-06-27 16:11:32 +03:00
printJSON :: (A.ToJSON a) => a -> IO ()
printJSON = BLC.putStrLn . A.encode
printYaml :: (A.ToJSON a) => a -> IO ()
printYaml = BC.putStrLn . Y.encode
parseEnvAsBool :: String -> IO Bool
parseEnvAsBool envVar = do
mVal <- fmap T.pack <$> lookupEnv envVar
maybe (return False) (parseAsBool . T.toLower) mVal
where
truthVals = ["true", "t", "yes", "y"]
falseVals = ["false", "f", "no", "n"]
parseAsBool t
| t `elem` truthVals = return True
| t `elem` falseVals = return False
| otherwise = putStrLn errMsg >> exitFailure
errMsg = "Fatal Error: " ++ envVar
++ " is not valid boolean text. " ++ "True values are "
++ show truthVals ++ " and False values are " ++ show falseVals
++ ". All values are case insensitive"
2018-06-27 16:11:32 +03:00
main :: IO ()
main = do
2018-06-27 16:11:32 +03:00
(RavenOptions rci ravenMode) <- parseArgs
mEnvDbUrl <- lookupEnv "HASURA_GRAPHQL_DATABASE_URL"
ci <- either ((>> exitFailure) . putStrLn . connInfoErrModifier)
return $ mkConnInfo mEnvDbUrl rci
2018-06-27 16:11:32 +03:00
printConnInfo ci
loggerCtx <- mkLoggerCtx $ defaultLoggerSettings True
hloggerCtx <- mkLoggerCtx $ defaultLoggerSettings False
httpManager <- HTTP.newManager HTTP.tlsManagerSettings
2018-06-27 16:11:32 +03:00
case ravenMode of
ROServe (ServeOptions mPort cp isoL mRootDir mAccessKey authHookC mJwtSecret
mUnAuthRole corsCfg enableConsole) -> do
-- get all auth mode related config
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
mFinalAccessKey <- considerEnv "HASURA_GRAPHQL_ACCESS_KEY" $ getAccessKey <$> mAccessKey
mFinalAuthHook <- mkAuthHook authHookC
add support for jwt authorization (close #186) (#255) The API: 1. HGE has `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var. The value of which is a JSON. 2. The structure of this JSON is: `{"type": "<standard-JWT-algorithms>", "key": "<the-key>"}` `type` : Standard JWT algos : `HS256`, `RS256`, `RS512` etc. (see jwt.io). `key`: i. Incase of symmetric key, the key as it is. ii. Incase of asymmetric keys, only the public key, in a PEM encoded string or as a X509 certificate. 3. The claims in the JWT token must contain the following: i. `x-hasura-default-role` field: default role of that user ii. `x-hasura-allowed-roles` : A list of allowed roles for the user. The default role is overriden by `x-hasura-role` header. 4. The claims in the JWT token, can have other `x-hasura-*` fields where their values can only be strings. 5. The JWT tokens are sent as `Authorization: Bearer <token>` headers. --- To test: 1. Generate a shared secret (for HMAC-SHA256) or RSA key pair. 2. Goto https://jwt.io/ , add the keys 3. Edit the claims to have `x-hasura-role` (mandatory) and other `x-hasura-*` fields. Add permissions related to the claims to test permissions. 4. Start HGE with `--jwt-secret` flag or `HASURA_GRAPHQL_JWT_SECRET` env var, which takes a JSON string: `{"type": "HS256", "key": "mylongsharedsecret"}` or `{"type":"RS256", "key": "<PEM-encoded-public-key>"}` 5. Copy the JWT token from jwt.io and use it in the `Authorization: Bearer <token>` header. --- TODO: Support EC public keys. It is blocked on frasertweedale/hs-jose#61
2018-08-30 13:32:09 +03:00
mFinalJwtSecret <- considerEnv "HASURA_GRAPHQL_JWT_SECRET" mJwtSecret
mFinalUnAuthRole <- considerEnv "HASURA_GRAPHQL_UNAUTHORIZED_ROLE" $ getRoleTxt <$> mUnAuthRole
defaultPort <- getFromEnv 8080 "HASURA_GRAPHQL_SERVER_PORT"
let port = fromMaybe defaultPort mPort
-- prepare auth mode
-- use webhook post config
authModeRes <- runExceptT $ mkAuthMode (AccessKey <$> mFinalAccessKey)
mFinalAuthHook
mFinalJwtSecret
(RoleName <$> mFinalUnAuthRole)
httpManager
loggerCtx
am <- either ((>> exitFailure) . putStrLn . T.unpack) return authModeRes
finalCorsDomain <- fromMaybe "*" <$> considerEnv "HASURA_GRAPHQL_CORS_DOMAIN" (ccDomain corsCfg)
let finalCorsCfg = CorsConfigG finalCorsDomain $ ccDisabled corsCfg
-- enable console config
finalEnableConsole <-
considerBoolEnv "HASURA_GRAPHQL_ENABLE_CONSOLE" enableConsole
-- init catalog if necessary
initialise ci httpManager
-- migrate catalog if necessary
migrate ci httpManager
2018-09-05 14:26:46 +03:00
prepareEvents ci
2018-06-27 16:11:32 +03:00
pool <- Q.initPGPool ci cp
putStrLn $ "server: running on port " ++ show port
(app, cacheRef) <- mkWaiApp isoL mRootDir loggerCtx pool httpManager
am finalCorsCfg finalEnableConsole
let warpSettings = Warp.setPort port Warp.defaultSettings
-- Warp.setHost "*" Warp.defaultSettings
-- start a background thread to check for updates
void $ C.forkIO $ checkForUpdates loggerCtx httpManager
2018-09-05 14:26:46 +03:00
maxEvThrds <- getFromEnv defaultMaxEventThreads "HASURA_GRAPHQL_EVENTS_HTTP_POOL_SIZE"
evFetchMilliSec <- getFromEnv defaultFetchIntervalMilliSec "HASURA_GRAPHQL_EVENTS_FETCH_INTERVAL"
logEnvHeaders <- getFromEnv False "LOG_HEADERS_FROM_ENV"
2018-09-05 14:26:46 +03:00
eventEngineCtx <- atomically $ initEventEngineCtx maxEvThrds evFetchMilliSec
2018-09-05 14:26:46 +03:00
httpSession <- WrqS.newSessionControl Nothing TLS.tlsManagerSettings
void $ C.forkIO $ processEventQueue hloggerCtx logEnvHeaders httpSession pool cacheRef eventEngineCtx
2018-09-05 14:26:46 +03:00
Warp.runSettings warpSettings app
2018-06-27 16:11:32 +03:00
ROExport -> do
res <- runTx ci fetchMetadata
either ((>> exitFailure) . printJSON) printJSON res
ROClean -> do
res <- runTx ci cleanCatalog
either ((>> exitFailure) . printJSON) (const cleanSuccess) res
ROExecute -> do
queryBs <- BL.getContents
res <- runTx ci $ execQuery httpManager queryBs
2018-06-27 16:11:32 +03:00
either ((>> exitFailure) . printJSON) BLC.putStrLn res
where
runTx ci tx = do
pool <- getMinimalPool ci
runExceptT $ Q.runTx pool (Q.Serializable, Nothing) tx
getMinimalPool ci = do
let connParams = Q.defaultConnParams { Q.cpConns = 1 }
Q.initPGPool ci connParams
initialise ci httpMgr = do
2018-06-27 16:11:32 +03:00
currentTime <- getCurrentTime
res <- runTx ci $ initCatalogSafe currentTime httpMgr
2018-06-27 16:11:32 +03:00
either ((>> exitFailure) . printJSON) putStrLn res
migrate ci httpMgr = do
2018-06-27 16:11:32 +03:00
currentTime <- getCurrentTime
res <- runTx ci $ migrateCatalog httpMgr currentTime
2018-06-27 16:11:32 +03:00
either ((>> exitFailure) . printJSON) putStrLn res
2018-09-05 14:26:46 +03:00
prepareEvents ci = do
putStrLn "event_triggers: preparing data"
res <- runTx ci unlockAllEvents
either ((>> exitFailure) . printJSON) return res
2018-09-05 14:26:46 +03:00
getFromEnv :: (Read a) => a -> String -> IO a
getFromEnv defaults env = do
mEnv <- lookupEnv env
let mRes = case mEnv of
Nothing -> Just defaults
Just val -> readMaybe val
eRes = maybe (Left $ "Wrong expected type for environment variable: " <> env) Right mRes
2018-09-05 14:26:46 +03:00
either ((>> exitFailure) . putStrLn) return eRes
2018-06-27 16:11:32 +03:00
cleanSuccess = putStrLn "successfully cleaned graphql-engine related data"
2018-06-27 16:11:32 +03:00
printConnInfo ci =
putStrLn $
"Postgres connection info:"
++ "\n Host: " ++ Q.connHost ci
++ "\n Port: " ++ show (Q.connPort ci)
++ "\n User: " ++ Q.connUser ci
++ "\n Database: " ++ Q.connDatabase ci
mkAuthHook (AuthHookG mUrl mTy) = do
url <- considerEnv "HASURA_GRAPHQL_AUTH_HOOK" mUrl
ty <- maybe getHookTypeEnv return mTy
return $ AuthHookG <$> url <*> pure ty
getHookTypeEnv = do
let envVar = "HASURA_GRAPHQL_AUTH_HOOK_MODE"
errorFn s = putStrLn (s ++ " for Env " ++ envVar)
>> exitFailure
mEnvVal <- lookupEnv "HASURA_GRAPHQL_AUTH_HOOK_MODE"
case mEnvVal of
Just s -> either errorFn return $ readHookType s
Nothing -> return AHTGet
-- if flags given are Nothing consider it's value from Env
considerEnv _ (Just t) = return $ Just t
considerEnv e Nothing = fmap T.pack <$> lookupEnv e
considerBoolEnv envVar =
bool (parseEnvAsBool envVar) (return True)