graphql-engine/server/src-lib/Hasura/SQL/AnyBackend.hs

Ignoring revisions in .git-blame-ignore-revs. Click here to bypass and see the normal blame view.

539 lines
20 KiB
Haskell
Raw Normal View History

{-# LANGUAGE Arrows #-}
{-# LANGUAGE UndecidableInstances #-}
-- | Dispatch over backends.
--
-- = Creating and consuming 'AnyBackend'
--
-- Creating a new value of type 'AnyBackend' is done via 'mkAnyBackend'.
--
-- Consuming a value of type 'AnyBackend' is done via either 'runAnyBackend' or
-- any of the dispatch functions ('dispatchAnyBackend', 'dispatchAnyBackend'',
-- 'dispatchAnyBackend''').
--
-- For implementation details, or when trying to understand this module, start
-- from 'AnyBackend'.
--
-- = Backend Architecture
--
-- Our multiple backend architecture uses type classes and associated types
-- in order to share code, such as parsing graphql queries, building
-- schemas and metadata, while still accounting for the differences between
-- backends.
--
-- Each backend implements the @Backend@ type class from "Hasura.RQL.Types.Backend"
-- as well as instances for other classes such as @BackendSchema@ from
-- "Hasura.GraphQL.Schema.Backend", and define the associated types and
-- functions, such as @ScalarType@ and @parseScalarValue@, which fit the backend.
--
-- Whenever one of these associated types (@ScalarType@, @Column@, etc.) are
-- used, we need to either push the 'BackendType' to our caller (and making our
-- type @BackendType -> Type@), or use 'AnyBackend' (and allow our type to be
-- 'Type'). This is particularly useful when we need to store a container of
-- any backend.
--
-- In order to actually program abstractly using type classes, we need the
-- type class instances to be available for us to use. This module is a trick
-- to enumerate all supported backends and their respective instances to convince
-- GHC that they can be used.
--
-- = Example usage
--
-- As an example of using this module, consider wanting to write a function
-- that calculates metrics for each source. For example, we want to count
-- the number of tables each source has.
--
-- The @SchemaCache@ (defined in "Hasura.RQL.Types.SchemaCache") holds a hash map
-- from each source to their information.
-- The source information is parameterized by the 'BackendType' and is hidden
-- using an existential type inside 'AnyBackend'. It essentially looks like this:
--
-- > data SourceInfo b = ...
-- >
-- > type SourceCache = HashMap SourceName (AnyBackend SourceInfo)
--
-- Our metrics calculation function cares which backend it receives, but only
-- for its type class instances so it can call the relevant functions:
--
-- > telemetryForSource :: forall (b :: BackendType). SourceInfo b -> TelemetryPayload
--
-- In order to apply this function to all backends and return the telemetry payload for each,
-- we need to map over the hash map and dispatch the function over the relevant backend.
-- we can do this with 'runBackend':
--
-- > telemetries =
-- > map
-- > (`runBackend` telemetryForSource)
-- > (scSources schemaCache)
--
-- If we want to be able to extract some information about the backend type
-- inside @telemetryForSource@, we can do this using 'backendTag':
--
-- > let telemetryForSource :: forall (b :: BackendType). HasTag b => SourceInfo b -> TelemetryPayload
-- > telemetryForSource =
-- > let dbKind = reify (backendTag @b)
--
-- Note that we needed to add the 'HasTag' constraint, which now means we can't use 'runBackend'
-- because our function has the wrong type (it has an extra constraint).
-- Instead, we can use 'dispatchAnyBackend' which allows us to have one constraint:
--
-- > telemetries =
-- > fmap
-- > (\sourceinfo -> (Any.dispatchAnyBackend @HasTag) sourceinfo telemetryForSource)
-- > (scSources schemaCache)
--
-- Note that we had to add the constraint name as a type application, and we had
-- to explicitly add a lambda instead of using 'flip'.
module Hasura.SQL.AnyBackend
( AnyBackend,
SatisfiesForAllBackends,
liftTag,
lowerTag,
mkAnyBackend,
mapBackend,
traverseBackend,
dispatchAnyBackend,
dispatchAnyBackend',
dispatchAnyBackend'',
dispatchAnyBackendArrow,
dispatchAnyBackendWithTwoConstraints,
mergeAnyBackend,
unpackAnyBackend,
composeAnyBackend,
runBackend,
parseAnyBackendFromJSON,
anyBackendCodec,
debugAnyBackendToJSON,
backendSourceKindFromText,
parseBackendSourceKindFromJSON,
)
where
import Autodocodec (HasCodec (codec), JSONCodec, dimapCodec)
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
import Control.Applicative
import Control.Arrow.Extended (ArrowChoice)
import Control.Lens (preview, _Right)
[gardening] Introduce PartialArbitrary ### Context One of the ways we use the Backend type families is to use `Void` for all types for which a backend has no representation; this allows us to make some branches of our metadata and IR unrepresentable, making some functions total, where they would have to handle those unsupported cases otherwise. However, one of the biggest features, functions, cannot be cut that way, due to one of the constraints on `FunctionName b`: the metadata generator requires it to have an `Arbitrary` instance, and `Arbitrary` does not have a recovery mechanism which would allow for a `Void` instance... ### Description This PR solves this problem and removes the `Arbitrary` constraints in `Backend`. To do so, it introduces a new typeclass: `PartialArbitrary`, which is very similar to `Arbitrary`, except that it returns a `Maybe (Gen a)`, allowing for `Void` to have a well-formed instance. An `Arbitrary` instance for `Metadata` can easily be retrieved with `arbitrary = fromJust . partialArbitrary`. Furthermore, `PartialArbitrary` has a generic implementation, inspired by the one in `generic-arbitrary`, which automatically prunes branches that return `Nothing`, allowing to automatically construct most types. Types that don't have a type parameter and therefore can't contain `Void` can easily get their `PartialArbitrary` instance from `Arbitrary` with `partialArbitrary = Just arbitrary`. This is what a default overlappable instance provides. In conjunction with other cleanups in #1666, **this allows for Void function names**. ### Notes While this solves the stated problem, there are other possible solutions we could explore, such as: - switching from QuickCheck to a library that supports that kind of pruning natively - removing the test altogether, and dropping all notion of Arbitrary from the code There are also several things we could do with the Generator module: - move it out of RQL.DDL.Metadata, to some place that makes more sense - move ALL Arbitrary instances in the code to it, since nothing else uses Arbitrary - or, to the contrary, move all those Arbitrary instances alongside their types, to avoid an orphan instance https://github.com/hasura/graphql-engine-mono/pull/1667 GitOrigin-RevId: 88e304ea453840efb5c0d39294639b8b30eefb81
2021-07-06 01:03:48 +03:00
import Data.Aeson
server: plumb `StoredIntrospection` while building the Schema Cache We'd like to be able to build a Schema Cache from only serializable data. We already have Metadata. The data that's missing to build a Schema Cache is referred to as "stored introspection", and this includes: - DB introspection - User-defined enum values (i.e. contents of specific DB tables) - Remote schema introspection This PR introduces a new `StoredIntrospection` container that holds that data, and plumbs it through to the right parts of the schema cache building process, so that stored introspection can be used as a substitute for fresh introspection requests against live data sources. The serialization of `StoredIntrospection` is intended to be straightforward: just take the serialized source introspection results, and put them in an appropriate JSON object. Though I don't think that this PR achieves that entirely. In order for `StoredIntrospection` to be deserializable (through `aeson` instances), while keeping the required code changes low, this piggy-backs off of the `ResolvedSource` data type. `ResolvedSource` is _almost_ exactly what we want, and _almost_ deserializable, so this PR brings it across the finish line by moving a few things out of that type, and adding a `FromJSON (RawFunctionInfo b)` context to the `Backend` type class. [PLAT-270]: https://hasurahq.atlassian.net/browse/PLAT-270?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ [PLAT-270]: https://hasurahq.atlassian.net/browse/PLAT-270?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ [PLAT-276]: https://hasurahq.atlassian.net/browse/PLAT-276?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ [PLAT-276]: https://hasurahq.atlassian.net/browse/PLAT-276?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7053 GitOrigin-RevId: 5001b4ea086195cb5e65886747eac2a0a657b64c
2023-01-20 17:51:11 +03:00
import Data.Aeson.Extended
import Data.Aeson.Key qualified as Key
import Data.Aeson.Types (Parser)
import Data.Kind (Constraint, Type)
import Hasura.Prelude
import Hasura.RQL.Types.BackendTag
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.DataConnector (mkDataConnectorName)
import Language.GraphQL.Draft.Syntax qualified as GQL
--------------------------------------------------------------------------------
-- * Types and constraints
-- | Allows storing types of kind @BackendType -> Type@ heterogenously.
--
-- Adding a new constructor to 'BackendType' will automatically create a new
-- constructor here.
--
-- Given some type defined as @data T (b :: BackendType) = ...@, we can define
-- @AnyBackend T@ without mentioning any 'BackendType'.
--
-- This is useful for having generic containers of potentially different types
-- of T. For instance, @SourceCache@ is defined as a
-- @HashMap SourceName (AnyBackend SourceInfo)@.
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
data AnyBackend (i :: BackendType -> Type)
= PostgresVanillaValue (i ('Postgres 'Vanilla))
| PostgresCitusValue (i ('Postgres 'Citus))
| PostgresCockroachValue (i ('Postgres 'Cockroach))
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
| MSSQLValue (i 'MSSQL)
| BigQueryValue (i 'BigQuery)
| DataConnectorValue (i 'DataConnector)
deriving (Generic)
-- | Generates a constraint for all backends.
type AllBackendsSatisfy (c :: BackendType -> Constraint) =
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
( c ('Postgres 'Vanilla),
c ('Postgres 'Citus),
c ('Postgres 'Cockroach),
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
c 'MSSQL,
c 'BigQuery,
c 'DataConnector
)
-- | Generates a constraint for a generic type over all backends.
type SatisfiesForAllBackends
(i :: BackendType -> Type)
(c :: Type -> Constraint) =
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
( c (i ('Postgres 'Vanilla)),
c (i ('Postgres 'Citus)),
c (i ('Postgres 'Cockroach)),
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
c (i 'MSSQL),
c (i 'BigQuery),
c (i 'DataConnector)
)
--------------------------------------------------------------------------------
-- * Functions on AnyBackend
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
-- | How to obtain a tag from a runtime value.
liftTag :: BackendType -> AnyBackend BackendTag
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
liftTag (Postgres Vanilla) = PostgresVanillaValue PostgresVanillaTag
liftTag (Postgres Citus) = PostgresCitusValue PostgresCitusTag
liftTag (Postgres Cockroach) = PostgresCockroachValue PostgresCockroachTag
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
liftTag MSSQL = MSSQLValue MSSQLTag
liftTag BigQuery = BigQueryValue BigQueryTag
liftTag DataConnector = DataConnectorValue DataConnectorTag
-- | Obtain a @BackendType@ from a runtime value.
lowerTag :: AnyBackend i -> BackendType
lowerTag (PostgresVanillaValue _) = Postgres Vanilla
lowerTag (PostgresCitusValue _) = Postgres Citus
lowerTag (PostgresCockroachValue _) = Postgres Cockroach
lowerTag (MSSQLValue _) = MSSQL
lowerTag (BigQueryValue _) = BigQuery
lowerTag (DataConnectorValue _) = DataConnector
-- | Transforms an @AnyBackend i@ into an @AnyBackend j@.
mapBackend ::
forall
(i :: BackendType -> Type)
(j :: BackendType -> Type).
AnyBackend i ->
(forall b. i b -> j b) ->
AnyBackend j
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
mapBackend e f = case e of
PostgresVanillaValue x -> PostgresVanillaValue (f x)
PostgresCitusValue x -> PostgresCitusValue (f x)
PostgresCockroachValue x -> PostgresCockroachValue (f x)
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue x -> MSSQLValue (f x)
BigQueryValue x -> BigQueryValue (f x)
DataConnectorValue x -> DataConnectorValue (f x)
-- | Traverse an @AnyBackend i@ into an @f (AnyBackend j)@.
traverseBackend ::
forall
(c :: BackendType -> Constraint)
(i :: BackendType -> Type)
(j :: BackendType -> Type)
f.
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
(AllBackendsSatisfy c, Functor f) =>
AnyBackend i ->
(forall b. (c b) => i b -> f (j b)) ->
f (AnyBackend j)
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
traverseBackend e f = case e of
PostgresVanillaValue x -> PostgresVanillaValue <$> f x
PostgresCitusValue x -> PostgresCitusValue <$> f x
PostgresCockroachValue x -> PostgresCockroachValue <$> f x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue x -> MSSQLValue <$> f x
BigQueryValue x -> BigQueryValue <$> f x
DataConnectorValue x -> DataConnectorValue <$> f x
-- | Creates a new @AnyBackend i@ for a given backend @b@ by wrapping the given @i b@.
mkAnyBackend ::
forall
(b :: BackendType)
(i :: BackendType -> Type).
(HasTag b) =>
i b ->
AnyBackend i
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
mkAnyBackend x = case backendTag @b of
PostgresVanillaTag -> PostgresVanillaValue x
PostgresCitusTag -> PostgresCitusValue x
PostgresCockroachTag -> PostgresCockroachValue x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLTag -> MSSQLValue x
BigQueryTag -> BigQueryValue x
DataConnectorTag -> DataConnectorValue x
-- | Dispatch a function to the value inside the @AnyBackend@, that does not
-- require bringing into scope a new class constraint.
runBackend ::
forall
(i :: BackendType -> Type)
(r :: Type).
AnyBackend i ->
(forall (b :: BackendType). i b -> r) ->
r
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
runBackend b f = case b of
PostgresVanillaValue x -> f x
PostgresCitusValue x -> f x
PostgresCockroachValue x -> f x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue x -> f x
BigQueryValue x -> f x
DataConnectorValue x -> f x
-- | Dispatch an existential using an universally quantified function while
-- also resolving a different constraint.
-- Use this to dispatch Backend* instances.
-- This is essentially a wrapper around @runAnyBackend f . repackAnyBackend \@c@.
dispatchAnyBackend ::
forall
(c :: BackendType -> Constraint)
(i :: BackendType -> Type)
(r :: Type).
(AllBackendsSatisfy c) =>
AnyBackend i ->
(forall (b :: BackendType). (c b) => i b -> r) ->
r
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
dispatchAnyBackend e f = case e of
PostgresVanillaValue x -> f x
PostgresCitusValue x -> f x
PostgresCockroachValue x -> f x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue x -> f x
BigQueryValue x -> f x
DataConnectorValue x -> f x
dispatchAnyBackendWithTwoConstraints ::
forall
(c1 :: BackendType -> Constraint)
(c2 :: BackendType -> Constraint)
(i :: BackendType -> Type)
(r :: Type).
(AllBackendsSatisfy c1) =>
(AllBackendsSatisfy c2) =>
AnyBackend i ->
(forall (b :: BackendType). (c1 b) => (c2 b) => i b -> r) ->
r
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
dispatchAnyBackendWithTwoConstraints e f = case e of
PostgresVanillaValue x -> f x
PostgresCitusValue x -> f x
PostgresCockroachValue x -> f x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue x -> f x
BigQueryValue x -> f x
DataConnectorValue x -> f x
-- | Unlike 'dispatchAnyBackend', the expected constraint has a different kind.
-- Use for classes like 'Show', 'ToJSON', etc.
dispatchAnyBackend' ::
forall
(c :: Type -> Constraint)
(i :: BackendType -> Type)
(r :: Type).
(i `SatisfiesForAllBackends` c) =>
AnyBackend i ->
(forall (b :: BackendType). (c (i b)) => i b -> r) ->
r
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
dispatchAnyBackend' e f = case e of
PostgresVanillaValue x -> f x
PostgresCitusValue x -> f x
PostgresCockroachValue x -> f x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue x -> f x
BigQueryValue x -> f x
DataConnectorValue x -> f x
-- | This allows you to apply a constraint to the Backend instances (c2)
-- as well as a constraint on the higher-kinded @i b@ type (c1)
dispatchAnyBackend'' ::
forall
(c1 :: Type -> Constraint)
(c2 :: BackendType -> Constraint)
(i :: BackendType -> Type)
(r :: Type).
(i `SatisfiesForAllBackends` c1) =>
(AllBackendsSatisfy c2) =>
AnyBackend i ->
(forall (b :: BackendType). (c2 b) => (c1 (i b)) => i b -> r) ->
r
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
dispatchAnyBackend'' e f = case e of
PostgresVanillaValue x -> f x
PostgresCitusValue x -> f x
PostgresCockroachValue x -> f x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue x -> f x
BigQueryValue x -> f x
DataConnectorValue x -> f x
-- | Sometimes we need to run operations on two backends of the same type.
-- If the backends don't contain the same type, the given @r@ value is returned.
-- Otherwise, the function is called with the two wrapped values.
composeAnyBackend ::
forall
(c :: BackendType -> Constraint)
(i :: BackendType -> Type)
(r :: Type).
(AllBackendsSatisfy c) =>
(forall (b :: BackendType). (c b) => i b -> i b -> r) ->
AnyBackend i ->
AnyBackend i ->
r ->
r
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
composeAnyBackend f e1 e2 owise = case (e1, e2) of
(PostgresVanillaValue x, PostgresVanillaValue y) -> f x y
(PostgresCitusValue x, PostgresCitusValue y) -> f x y
(PostgresCockroachValue x, PostgresCockroachValue y) -> f x y
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
(MSSQLValue x, MSSQLValue y) -> f x y
(BigQueryValue x, BigQueryValue y) -> f x y
(DataConnectorValue x, DataConnectorValue y) -> f x y
(value1, value2) ->
if mapBackend value1 (Const . const ()) == mapBackend value2 (Const . const ())
then error "Programming error: missing case in composeAnyBackend"
else owise
-- | Merge two matching backends, falling back on a default.
mergeAnyBackend ::
forall
(c :: Type -> Constraint)
(i :: BackendType -> Type).
(i `SatisfiesForAllBackends` c) =>
(forall (b :: BackendType). (c (i b)) => i b -> i b -> i b) ->
AnyBackend i ->
AnyBackend i ->
AnyBackend i ->
AnyBackend i
mergeAnyBackend f e1 e2 owise = case (e1, e2) of
(PostgresVanillaValue x, PostgresVanillaValue y) -> PostgresVanillaValue (f x y)
(PostgresCitusValue x, PostgresCitusValue y) -> PostgresCitusValue (f x y)
(PostgresCockroachValue x, PostgresCockroachValue y) -> PostgresCockroachValue (f x y)
(MSSQLValue x, MSSQLValue y) -> MSSQLValue (f x y)
(BigQueryValue x, BigQueryValue y) -> BigQueryValue (f x y)
(DataConnectorValue x, DataConnectorValue y) -> DataConnectorValue (f x y)
(value1, value2) ->
if mapBackend value1 (Const . const ()) == mapBackend value2 (Const . const ())
then error "Programming error: missing case in mergeAnyBackend"
else owise
-- | Try to unpack the type of an existential.
-- Returns @Just x@ upon a succesful match, @Nothing@ otherwise.
unpackAnyBackend ::
forall
(b :: BackendType)
(i :: BackendType -> Type).
(HasTag b) =>
AnyBackend i ->
Maybe (i b)
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
unpackAnyBackend exists = case (backendTag @b, exists) of
(PostgresVanillaTag, PostgresVanillaValue x) -> Just x
(PostgresCitusTag, PostgresCitusValue x) -> Just x
(PostgresCockroachTag, PostgresCockroachValue x) -> Just x
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
(MSSQLTag, MSSQLValue x) -> Just x
(BigQueryTag, BigQueryValue x) -> Just x
(DataConnectorTag, DataConnectorValue x) -> Just x
(tag, value) ->
if mapBackend (mkAnyBackend tag) (Const . const ()) == mapBackend value (Const . const ())
then error "Programming error: missing case in unpackAnyBackend"
else Nothing
--------------------------------------------------------------------------------
--
-- * Special case for arrows
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
-- | Dispatch variant for use with arrow syntax.
--
-- NOTE: The below function accepts two constraints, if the arrow
-- you want to dispatch only has one constraint then repeat the constraint twice.
-- For example:
--
-- > AB.dispatchAnyBackendArrow @BackendMetadata @BackendMetadata (proc (sourceMetadata, invalidationKeys)
dispatchAnyBackendArrow ::
forall
(c1 :: BackendType -> Constraint)
(c2 :: BackendType -> Constraint)
(i :: BackendType -> Type)
(r :: Type)
(arr :: Type -> Type -> Type)
x.
(ArrowChoice arr, AllBackendsSatisfy c1, AllBackendsSatisfy c2) =>
(forall b. (c1 b) => (c2 b) => arr (i b, x) r) ->
arr (AnyBackend i, x) r
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
dispatchAnyBackendArrow arrow = proc (ab, x) -> do
case ab of
PostgresVanillaValue val ->
arrow @('Postgres 'Vanilla) -< (val, x)
PostgresCitusValue val ->
arrow @('Postgres 'Citus) -< (val, x)
PostgresCockroachValue val ->
arrow @('Postgres 'Cockroach) -< (val, x)
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQLValue val ->
arrow @'MSSQL -< (val, x)
BigQueryValue val ->
arrow @'BigQuery -< (val, x)
DataConnectorValue val ->
arrow @'DataConnector -< (val, x)
--------------------------------------------------------------------------------
-- * JSON functions
-- | Attempts to parse an 'AnyBackend' from a JSON value, using the provided
-- backend information.
parseAnyBackendFromJSON ::
(i `SatisfiesForAllBackends` FromJSON) =>
BackendType ->
Value ->
Parser (AnyBackend i)
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
parseAnyBackendFromJSON backendKind value = case backendKind of
Postgres Vanilla -> PostgresVanillaValue <$> parseJSON value
Postgres Citus -> PostgresCitusValue <$> parseJSON value
Postgres Cockroach -> PostgresCockroachValue <$> parseJSON value
Spell out the TH in `Hasura.SQL.{Tag,AnyBackend}` The module `Hasura.SQL.AnyBackend` was introduced (in #751) to centralize the logic for case-switching behavior that depends on the particular flavor of relational DB backend (Postgres vs MSSQL vs BigQuery vs MySQL vs DataConnectors). This allows us to write a bunch of code in a backend-agnostic way, even if runtime behavior does depend on the chosen backend. At the same time, it allows us to write backend-specific code without having to care (too much) about the existence of other backends. In #851 this module was rewritten to use Template Haskell. I've heard that one of the reasons for the use of TH was that this would make it easier to keep backends out of the compilation product entirely. This would allow customers, especially on OSS, to benefit from simpler software licensing. However: 1. This conditional compilation never materialized. 2. It's not clear whether writing this particular module based on TH would be sufficient for conditional compilation. And in any case, it can be done using CPP pragmas as well. 3. The TH code is extraordinarily complex. Since its introduction, it has been documented extraordinarily well, but it's still very difficult to maintain and/or refactor, due to its non-idiomatic nature. 4. Hasura's company objectives are now Cloud-oriented, so that software licensing issues work differently, and in particular, do not depend on what's part of the compilation product. So this PR reverts on #851 by spelling out the code generated by TH. This is a net-negative diff size. IOW we used to generate less code than the size of the code doing the generating. This makes the code readable and maintainable. The generated code has been modified in one way, which I'll now describe. In the scenario that support for a new backend is introduced, a constructor is added to the `BackendType` type. This would then cause `liftTag` to be partial, thus raising a compiler warning. Resolving this requires adding corresponding constructors to the `BackendTag` and `AnyBackend` types. This would then require amending **almost** all other methods. The exceptions are `composeAnyBackend` and `unpackAnyBackend`. These methods test whether two values are compatible, i.e. belong to the same backend. Both have a default case that in one way or another ignores the input values. Using TH here ensures that all values that belong together are caught. But after spelling out the TH, the presence of the default case means that no compiler warning is thrown for a missing match of matching values. So in the default case, we now do an explicit check for equality. If there _is_ an equality, that means that there is a missing `case`. So this is reported as an `error` (which is very crude, but it should be). PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5333 GitOrigin-RevId: 5aaf0a93394bd740aa7371526d3175c8142b3541
2022-08-11 12:09:53 +03:00
MSSQL -> MSSQLValue <$> parseJSON value
BigQuery -> BigQueryValue <$> parseJSON value
DataConnector -> DataConnectorValue <$> parseJSON value
-- | Codec that can be used to decode and encode @AnyBackend i@ values. Throws
-- an error when attempting to encode a value with a mismatched @backendKind@
-- argument.
anyBackendCodec ::
forall i.
(i `SatisfiesForAllBackends` HasCodec) =>
BackendType ->
JSONCodec (AnyBackend i)
anyBackendCodec backendKind = case backendKind of
Postgres Vanilla -> dimapCodec PostgresVanillaValue (\case (PostgresVanillaValue v) -> v; _ -> error msg) $ codec @(i ('Postgres 'Vanilla))
Postgres Citus -> dimapCodec PostgresCitusValue (\case (PostgresCitusValue v) -> v; _ -> error msg) $ codec @(i ('Postgres 'Citus))
Postgres Cockroach -> dimapCodec PostgresCockroachValue (\case (PostgresCockroachValue v) -> v; _ -> error msg) $ codec @(i ('Postgres 'Cockroach))
MSSQL -> dimapCodec MSSQLValue (\case (MSSQLValue v) -> v; _ -> error msg) $ codec @(i 'MSSQL)
BigQuery -> dimapCodec BigQueryValue (\case (BigQueryValue v) -> v; _ -> error msg) $ codec @(i 'BigQuery)
DataConnector -> dimapCodec DataConnectorValue (\case (DataConnectorValue v) -> v; _ -> error msg) $ codec @(i 'DataConnector)
where
msg = "got unexpected backend type indicating anyBackendCodec was called with the wrong backendType value"
-- | Outputs a debug JSON value from an 'AnyBackend'. This function must only be
-- used for debug purposes, as it has no way of inserting the backend kind in
-- the output, since there's no guarantee that the output will be an object.
debugAnyBackendToJSON ::
(i `SatisfiesForAllBackends` ToJSON) =>
AnyBackend i ->
Value
debugAnyBackendToJSON e = dispatchAnyBackend' @ToJSON e toJSON
--------------------------------------------------------------------------------
-- * Instances for 'AnyBackend'
deriving instance (i `SatisfiesForAllBackends` Show) => Show (AnyBackend i)
deriving instance (i `SatisfiesForAllBackends` Eq) => Eq (AnyBackend i)
deriving instance (i `SatisfiesForAllBackends` Ord) => Ord (AnyBackend i)
instance (i `SatisfiesForAllBackends` Hashable) => Hashable (AnyBackend i)
instance (i `SatisfiesForAllBackends` FromJSON) => FromJSONKeyValue (AnyBackend i) where
server: plumb `StoredIntrospection` while building the Schema Cache We'd like to be able to build a Schema Cache from only serializable data. We already have Metadata. The data that's missing to build a Schema Cache is referred to as "stored introspection", and this includes: - DB introspection - User-defined enum values (i.e. contents of specific DB tables) - Remote schema introspection This PR introduces a new `StoredIntrospection` container that holds that data, and plumbs it through to the right parts of the schema cache building process, so that stored introspection can be used as a substitute for fresh introspection requests against live data sources. The serialization of `StoredIntrospection` is intended to be straightforward: just take the serialized source introspection results, and put them in an appropriate JSON object. Though I don't think that this PR achieves that entirely. In order for `StoredIntrospection` to be deserializable (through `aeson` instances), while keeping the required code changes low, this piggy-backs off of the `ResolvedSource` data type. `ResolvedSource` is _almost_ exactly what we want, and _almost_ deserializable, so this PR brings it across the finish line by moving a few things out of that type, and adding a `FromJSON (RawFunctionInfo b)` context to the `Backend` type class. [PLAT-270]: https://hasurahq.atlassian.net/browse/PLAT-270?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ [PLAT-270]: https://hasurahq.atlassian.net/browse/PLAT-270?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ [PLAT-276]: https://hasurahq.atlassian.net/browse/PLAT-276?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ [PLAT-276]: https://hasurahq.atlassian.net/browse/PLAT-276?atlOrigin=eyJpIjoiNWRkNTljNzYxNjVmNDY3MDlhMDU5Y2ZhYzA5YTRkZjUiLCJwIjoiZ2l0aHViLWNvbS1KU1cifQ PR-URL: https://github.com/hasura/graphql-engine-mono/pull/7053 GitOrigin-RevId: 5001b4ea086195cb5e65886747eac2a0a657b64c
2023-01-20 17:51:11 +03:00
parseJSONKeyValue (backendTypeStr, value) = do
backendType <- parseBackendTypeFromText $ Key.toText backendTypeStr
parseAnyBackendFromJSON backendType value
backendSourceKindFromText :: Text -> Maybe (AnyBackend BackendSourceKind)
backendSourceKindFromText text =
PostgresVanillaValue <$> staticKindFromText PostgresVanillaKind
<|> PostgresCitusValue <$> staticKindFromText PostgresCitusKind
<|> PostgresCockroachValue <$> staticKindFromText PostgresCockroachKind
<|> MSSQLValue <$> staticKindFromText MSSQLKind
<|> BigQueryValue <$> staticKindFromText BigQueryKind
-- IMPORTANT: This must be the last thing here, since it will accept (almost) any string
<|> DataConnectorValue . DataConnectorKind <$> (preview _Right . mkDataConnectorName =<< GQL.mkName text)
where
staticKindFromText :: BackendSourceKind b -> Maybe (BackendSourceKind b)
staticKindFromText kind =
if text `elem` backendTextNames (backendTypeFromBackendSourceKind kind)
then Just kind
else Nothing
parseBackendSourceKindFromJSON :: Value -> Parser (AnyBackend BackendSourceKind)
parseBackendSourceKindFromJSON value =
PostgresVanillaValue <$> parseJSON @(BackendSourceKind ('Postgres 'Vanilla)) value
<|> PostgresCitusValue <$> parseJSON @(BackendSourceKind ('Postgres 'Citus)) value
<|> PostgresCockroachValue <$> parseJSON @(BackendSourceKind ('Postgres 'Cockroach)) value
<|> MSSQLValue <$> parseJSON @(BackendSourceKind ('MSSQL)) value
<|> BigQueryValue <$> parseJSON @(BackendSourceKind ('BigQuery)) value
-- IMPORTANT: This must the last thing here, since it will accept (almost) any string
<|> DataConnectorValue <$> parseJSON @(BackendSourceKind ('DataConnector)) value