graphql-engine/server/src-lib/Hasura/RQL/DDL/Headers.hs
Robert 11a454c2d6 server, pro: actually reformat the code-base using ormolu
This commit applies ormolu to the whole Haskell code base by running `make format`.

For in-flight branches, simply merging changes from `main` will result in merge conflicts.
To avoid this, update your branch using the following instructions. Replace `<format-commit>`
by the hash of *this* commit.

$ git checkout my-feature-branch
$ git merge <format-commit>^    # and resolve conflicts normally
$ make format
$ git commit -a -m "reformat with ormolu"
$ git merge -s ours post-ormolu

https://github.com/hasura/graphql-engine-mono/pull/2404

GitOrigin-RevId: 75049f5c12f430c615eafb4c6b8e83e371e01c8e
2021-09-23 22:57:37 +00:00

71 lines
2.4 KiB
Haskell

module Hasura.RQL.DDL.Headers where
import Data.Aeson
import Data.CaseInsensitive qualified as CI
import Data.Environment qualified as Env
import Data.Text qualified as T
import Hasura.Base.Error
import Hasura.Base.Instances ()
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Network.HTTP.Types qualified as HTTP
data HeaderConf = HeaderConf HeaderName HeaderValue
deriving (Show, Eq, Generic)
instance NFData HeaderConf
instance Hashable HeaderConf
instance Cacheable HeaderConf
type HeaderName = Text
data HeaderValue = HVValue Text | HVEnv Text
deriving (Show, Eq, Generic)
instance NFData HeaderValue
instance Hashable HeaderValue
instance Cacheable HeaderValue
instance FromJSON HeaderConf where
parseJSON (Object o) = do
name <- o .: "name"
value <- o .:? "value"
valueFromEnv <- o .:? "value_from_env"
case (value, valueFromEnv) of
(Nothing, Nothing) -> fail "expecting value or value_from_env keys"
(Just val, Nothing) -> return $ HeaderConf name (HVValue val)
(Nothing, Just val) -> do
when (T.isPrefixOf "HASURA_GRAPHQL_" val) $
fail $ "env variables starting with \"HASURA_GRAPHQL_\" are not allowed in value_from_env: " <> T.unpack val
return $ HeaderConf name (HVEnv val)
(Just _, Just _) -> fail "expecting only one of value or value_from_env keys"
parseJSON _ = fail "expecting object for headers"
instance ToJSON HeaderConf where
toJSON (HeaderConf name (HVValue val)) = object ["name" .= name, "value" .= val]
toJSON (HeaderConf name (HVEnv val)) = object ["name" .= name, "value_from_env" .= val]
-- | Resolve configuration headers
makeHeadersFromConf ::
MonadError QErr m => Env.Environment -> [HeaderConf] -> m [HTTP.Header]
makeHeadersFromConf env = mapM getHeader
where
getHeader hconf =
((CI.mk . txtToBs) *** txtToBs)
<$> case hconf of
(HeaderConf name (HVValue val)) -> return (name, val)
(HeaderConf name (HVEnv val)) -> do
let mEnv = Env.lookupEnv env (T.unpack val)
case mEnv of
Nothing -> throw400 NotFound $ "environment variable '" <> val <> "' not set"
Just envval -> pure (name, T.pack envval)
-- | Encode headers to HeaderConf
toHeadersConf :: [HTTP.Header] -> [HeaderConf]
toHeadersConf =
map (uncurry HeaderConf . ((bsToTxt . CI.original) *** (HVValue . bsToTxt)))