graphql-engine/server/src-lib/Hasura/Server/Utils.hs

231 lines
7.6 KiB
Haskell
Raw Normal View History

{-# LANGUAGE TypeApplications #-}
2018-06-27 16:11:32 +03:00
module Hasura.Server.Utils where
import Data.Aeson
import Data.Char
import Data.List (find)
import Language.Haskell.TH.Syntax (Lift)
import System.Environment
import System.Exit
import System.Process
import qualified Data.ByteString as B
import qualified Data.CaseInsensitive as CI
import qualified Data.HashSet as Set
import qualified Data.List.NonEmpty as NE
import qualified Data.Text as T
import qualified Data.Text.Encoding as TE
import qualified Data.Text.IO as TI
import qualified Data.UUID as UUID
import qualified Data.UUID.V4 as UUID
import qualified Language.Haskell.TH.Syntax as TH
import qualified Network.HTTP.Client as HC
import qualified Network.HTTP.Types as HTTP
import qualified Text.Regex.TDFA as TDFA
import qualified Text.Regex.TDFA.ByteString as TDFA
2018-06-27 16:11:32 +03:00
import Hasura.Prelude
newtype RequestId
= RequestId { unRequestId :: Text }
deriving (Show, Eq, ToJSON, FromJSON)
jsonHeader :: (T.Text, T.Text)
jsonHeader = ("Content-Type", "application/json; charset=utf-8")
sqlHeader :: (T.Text, T.Text)
sqlHeader = ("Content-Type", "application/sql; charset=utf-8")
htmlHeader :: (T.Text, T.Text)
htmlHeader = ("Content-Type", "text/html; charset=utf-8")
gzipHeader :: (T.Text, T.Text)
gzipHeader = ("Content-Encoding", "gzip")
brHeader :: (T.Text, T.Text)
brHeader = ("Content-Encoding", "br")
2018-06-27 16:11:32 +03:00
userRoleHeader :: T.Text
userRoleHeader = "x-hasura-role"
deprecatedAccessKeyHeader :: T.Text
deprecatedAccessKeyHeader = "x-hasura-access-key"
adminSecretHeader :: T.Text
adminSecretHeader = "x-hasura-admin-secret"
userIdHeader :: T.Text
userIdHeader = "x-hasura-user-id"
requestIdHeader :: T.Text
requestIdHeader = "x-request-id"
getRequestHeader :: B.ByteString -> [HTTP.Header] -> Maybe B.ByteString
getRequestHeader hdrName hdrs = snd <$> mHeader
where
mHeader = find (\h -> fst h == CI.mk hdrName) hdrs
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
getRequestId :: (MonadIO m) => [HTTP.Header] -> m RequestId
getRequestId headers =
-- generate a request id for every request if the client has not sent it
case getRequestHeader (txtToBs requestIdHeader) headers of
Nothing -> RequestId <$> liftIO generateFingerprint
Just reqId -> return $ RequestId $ bsToTxt reqId
-- Get an env var during compile time
getValFromEnvOrScript :: String -> String -> TH.Q (TH.TExp String)
getValFromEnvOrScript n s = do
maybeVal <- TH.runIO $ lookupEnv n
case maybeVal of
Just val -> [|| val ||]
Nothing -> runScript s
-- Run a shell script during compile time
runScript :: FilePath -> TH.Q (TH.TExp String)
runScript fp = do
TH.addDependentFile fp
fileContent <- TH.runIO $ TI.readFile fp
(exitCode, stdOut, stdErr) <- TH.runIO $
readProcessWithExitCode "/bin/sh" [] $ T.unpack fileContent
when (exitCode /= ExitSuccess) $ fail $
"Running shell script " ++ fp ++ " failed with exit code : "
++ show exitCode ++ " and with error : " ++ stdErr
[|| stdOut ||]
-- find duplicates
duplicates :: Ord a => [a] -> [a]
duplicates = mapMaybe greaterThanOne . group . sort
where
greaterThanOne l = bool Nothing (Just $ head l) $ length l > 1
-- regex related
matchRegex :: B.ByteString -> Bool -> T.Text -> Either String Bool
matchRegex regex caseSensitive src =
fmap (`TDFA.match` TE.encodeUtf8 src) compiledRegexE
where
compOpt = TDFA.defaultCompOpt
{ TDFA.caseSensitive = caseSensitive
, TDFA.multiline = True
, TDFA.lastStarGreedy = True
}
execOption = TDFA.defaultExecOpt {TDFA.captureGroups = False}
compiledRegexE = TDFA.compile compOpt execOption regex
fmapL :: (a -> a') -> Either a b -> Either a' b
fmapL fn (Left e) = Left (fn e)
fmapL _ (Right x) = pure x
generateFingerprint :: IO Text
generateFingerprint = UUID.toText <$> UUID.nextRandom
-- json representation of HTTP exception
httpExceptToJSON :: HC.HttpException -> Value
httpExceptToJSON e = case e of
HC.HttpExceptionRequest x c ->
let reqObj = object
[ "host" .= bsToTxt (HC.host x)
, "port" .= show (HC.port x)
, "secure" .= HC.secure x
, "path" .= bsToTxt (HC.path x)
, "method" .= bsToTxt (HC.method x)
, "proxy" .= (showProxy <$> HC.proxy x)
, "redirectCount" .= show (HC.redirectCount x)
, "responseTimeout" .= show (HC.responseTimeout x)
, "requestVersion" .= show (HC.requestVersion x)
]
msg = show c
in object ["request" .= reqObj, "message" .= msg]
_ -> toJSON $ show e
where
showProxy (HC.Proxy h p) =
"host: " <> bsToTxt h <> " port: " <> T.pack (show p)
-- ignore the following request headers from the client
commonClientHeadersIgnored :: (IsString a) => [a]
commonClientHeadersIgnored =
[ "Content-Length", "Content-MD5", "User-Agent", "Host"
, "Origin", "Referer" , "Accept", "Accept-Encoding"
, "Accept-Language", "Accept-Datetime"
, "Cache-Control", "Connection", "DNT", "Content-Type"
]
commonResponseHeadersIgnored :: (IsString a) => [a]
commonResponseHeadersIgnored =
[ "Server", "Transfer-Encoding", "Cache-Control"
, "Access-Control-Allow-Credentials"
, "Access-Control-Allow-Methods"
, "Access-Control-Allow-Origin"
, "Content-Type", "Content-Length"
]
allow custom mutations through actions (#3042) * basic doc for actions * custom_types, sync and async actions * switch to graphql-parser-hs on github * update docs * metadata import/export * webhook calls are now supported * relationships in sync actions * initialise.sql is now in sync with the migration file * fix metadata tests * allow specifying arguments of actions * fix blacklist check on check_build_worthiness job * track custom_types and actions related tables * handlers are now triggered on async actions * default to pgjson unless a field is involved in relationships, for generating definition list * use 'true' for action filter for non admin role * fix create_action_permission sql query * drop permissions when dropping an action * add a hdb_role view (and relationships) to fetch all roles in the system * rename 'webhook' key in action definition to 'handler' * allow templating actions wehook URLs with env vars * add 'update_action' /v1/query type * allow forwarding client headers by setting `forward_client_headers` in action definition * add 'headers' configuration in action definition * handle webhook error response based on status codes * support array relationships for custom types * implement single row mutation, see https://github.com/hasura/graphql-engine/issues/3731 * single row mutation: rename 'pk_columns' -> 'columns' and no-op refactor * use top level primary key inputs for delete_by_pk & account select permissions for single row mutations * use only REST semantics to resolve the webhook response * use 'pk_columns' instead of 'columns' for update_by_pk input * add python basic tests for single row mutations * add action context (name) in webhook payload * Async action response is accessible for non admin roles only if the request session vars equals to action's * clean nulls, empty arrays for actions, custom types in export metadata * async action mutation returns only the UUID of the action * unit tests for URL template parser * Basic sync actions python tests * fix output in async query & add async tests * add admin secret header in async actions python test * document async action architecture in Resolve/Action.hs file * support actions returning array of objects * tests for list type response actions * update docs with actions and custom types metadata API reference * update actions python tests as per #f8e1330 Co-authored-by: Tirumarai Selvan <tirumarai.selvan@gmail.com> Co-authored-by: Aravind Shankar <face11301@gmail.com> Co-authored-by: Rakesh Emmadi <12475069+rakeshkky@users.noreply.github.com>
2020-02-13 20:38:23 +03:00
isUserVar :: Text -> Bool
isUserVar = T.isPrefixOf "x-hasura-" . T.toLower
mkClientHeadersForward :: [HTTP.Header] -> [HTTP.Header]
mkClientHeadersForward reqHeaders =
xForwardedHeaders <> (filterUserVars . filterRequestHeaders) reqHeaders
where
filterUserVars = filter (\(k, _) -> not $ isUserVar $ bsToTxt $ CI.original k)
xForwardedHeaders = flip mapMaybe reqHeaders $ \(hdrName, hdrValue) ->
case hdrName of
"Host" -> Just ("X-Forwarded-Host", hdrValue)
"User-Agent" -> Just ("X-Forwarded-User-Agent", hdrValue)
_ -> Nothing
filterRequestHeaders :: [HTTP.Header] -> [HTTP.Header]
filterRequestHeaders =
filterHeaders $ Set.fromList commonClientHeadersIgnored
-- ignore the following response headers from remote
filterResponseHeaders :: [HTTP.Header] -> [HTTP.Header]
filterResponseHeaders =
filterHeaders $ Set.fromList commonResponseHeadersIgnored
filterHeaders :: Set.HashSet HTTP.HeaderName -> [HTTP.Header] -> [HTTP.Header]
filterHeaders list = filter (\(n, _) -> not $ n `Set.member` list)
hyphenate :: String -> String
hyphenate = u . applyFirst toLower
where u [] = []
u (x:xs) | isUpper x = '-' : toLower x : hyphenate xs
| otherwise = x : u xs
applyFirst :: (Char -> Char) -> String -> String
applyFirst _ [] = []
applyFirst f [x] = [f x]
applyFirst f (x:xs) = f x: xs
-- | The version integer
data APIVersion
= VIVersion1
| VIVersion2
deriving (Show, Eq, Lift)
instance ToJSON APIVersion where
toJSON VIVersion1 = toJSON @Int 1
toJSON VIVersion2 = toJSON @Int 2
instance FromJSON APIVersion where
parseJSON v = do
verInt :: Int <- parseJSON v
case verInt of
1 -> return VIVersion1
2 -> return VIVersion2
i -> fail $ "expected 1 or 2, encountered " ++ show i
englishList :: NonEmpty Text -> Text
englishList = \case
one :| [] -> one
one :| [two] -> one <> " and " <> two
several ->
let final :| initials = NE.reverse several
in T.intercalate ", " (reverse initials) <> ", and " <> final
makeReasonMessage :: [a] -> (a -> Text) -> Text
makeReasonMessage errors showError =
case errors of
[singleError] -> "because " <> showError singleError
_ -> "for the following reasons:\n" <> T.unlines
(map (("" <>) . showError) errors)