graphql-engine/server/src-lib/Hasura/GraphQL/Parser/Column.hs
Rakesh Emmadi 9ef603360c server: generalize schema cache building (#496)
Co-authored-by: Vamshi Surabhi <vamshi@hasura.io>
Co-authored-by: Vladimir Ciobanu <admin@cvlad.info>
Co-authored-by: Antoine Leblanc <antoine@hasura.io>
Co-authored-by: Stylish Haskell Bot <stylish-haskell@users.noreply.github.com>
GitOrigin-RevId: 9d631878037637f3ed2994b5d0525efd978f7b8f
2021-02-14 06:08:46 +00:00

55 lines
1.8 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE StrictData #-}
module Hasura.GraphQL.Parser.Column
( UnpreparedValue(..)
, Opaque
, mkOpaque
, openOpaque
, mkParameter
) where
import Hasura.Prelude
import Hasura.GraphQL.Parser.Class
import Hasura.GraphQL.Parser.Schema
import Hasura.RQL.Types.Backend
import Hasura.RQL.Types.Column hiding (EnumValue (..), EnumValueInfo (..))
import Hasura.SQL.Backend
import Hasura.Session (SessionVariable)
-- -------------------------------------------------------------------------------------------------
data Opaque a = Opaque
{ _opVariable :: Maybe VariableInfo
-- ^ The variable this value came from, if any.
, _opValue :: a
} -- Note: we intentionally dont derive any instances here, since that would
-- defeat the opaqueness!
mkOpaque :: Maybe VariableInfo -> a -> Opaque a
mkOpaque = Opaque
openOpaque :: MonadParse m => Opaque a -> m a
openOpaque (Opaque Nothing value) = pure value
openOpaque (Opaque (Just _) value) = markNotReusable $> value
data UnpreparedValue (b :: BackendType)
-- | A SQL value that can be parameterized over.
= UVParameter
(Maybe VariableInfo)
-- ^ The GraphQL variable this value came from, if any.
(ColumnValue b)
-- | A literal SQL expression that /cannot/ be parameterized over.
| UVLiteral (SQLExpression b)
-- | The entire session variables JSON object.
| UVSession
-- | A single session variable.
| UVSessionVar (SessionVarType b) SessionVariable
-- FIXME exporting this method means doing away with the opaqueness of the
-- 'Opaque' data type, since the constructors of 'UnpreparedValue' are exported
-- globally.
mkParameter :: Opaque (ColumnValue b) -> UnpreparedValue b
mkParameter (Opaque variable value) = UVParameter variable value