2022-03-16 03:39:21 +03:00
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
2022-01-14 17:08:17 +03:00
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
|
2022-01-03 20:16:24 +03:00
|
|
|
-- | MSSQL Connection
|
|
|
|
--
|
|
|
|
-- This module handles the connection against an MS SQL Server.
|
|
|
|
-- It defines the connection string, connection pool, default settings,
|
|
|
|
-- and conversion functions between MSSQL and graphql-engine.
|
2021-11-04 19:08:33 +03:00
|
|
|
module Hasura.Backends.MSSQL.Connection
|
|
|
|
( MSSQLConnConfiguration (MSSQLConnConfiguration),
|
2023-04-05 11:57:19 +03:00
|
|
|
MSSQLSourceConfig (MSSQLSourceConfig, _mscExecCtx, _mscReadReplicas),
|
2022-09-02 09:33:21 +03:00
|
|
|
MSSQLConnectionInfo (..),
|
|
|
|
MSSQLPoolSettings (..),
|
2022-01-04 14:53:50 +03:00
|
|
|
MSSQLExecCtx (..),
|
2022-02-24 11:13:19 +03:00
|
|
|
MonadMSSQLTx (..),
|
2022-10-17 11:04:54 +03:00
|
|
|
defaultMSSQLMaxConnections,
|
2021-11-04 19:08:33 +03:00
|
|
|
createMSSQLPool,
|
2022-10-17 11:04:54 +03:00
|
|
|
resizeMSSQLPool,
|
2021-11-04 19:08:33 +03:00
|
|
|
getEnv,
|
|
|
|
odbcValueToJValue,
|
2022-01-04 14:53:50 +03:00
|
|
|
mkMSSQLExecCtx,
|
2022-09-02 09:33:21 +03:00
|
|
|
mkMSSQLAnyQueryTx,
|
2022-04-21 10:19:37 +03:00
|
|
|
runMSSQLSourceReadTx,
|
|
|
|
runMSSQLSourceWriteTx,
|
2021-11-04 19:08:33 +03:00
|
|
|
)
|
|
|
|
where
|
2021-02-23 20:37:27 +03:00
|
|
|
|
2022-10-12 19:28:51 +03:00
|
|
|
import Autodocodec (HasCodec (codec), dimapCodec, disjointEitherCodec, optionalFieldOrNull', optionalFieldWithDefault', requiredField')
|
|
|
|
import Autodocodec qualified as AC
|
2022-02-24 11:13:19 +03:00
|
|
|
import Control.Monad.Morph (hoist)
|
2021-10-22 17:49:15 +03:00
|
|
|
import Control.Monad.Trans.Control
|
2021-02-23 20:37:27 +03:00
|
|
|
import Data.Aeson
|
2021-10-01 15:52:19 +03:00
|
|
|
import Data.Aeson qualified as J
|
2021-02-23 20:37:27 +03:00
|
|
|
import Data.Aeson.TH
|
2021-07-23 15:25:16 +03:00
|
|
|
import Data.Environment qualified as Env
|
2021-03-18 21:32:47 +03:00
|
|
|
import Data.Text (pack, unpack)
|
2022-09-13 11:33:44 +03:00
|
|
|
import Data.Time (localTimeToUTC)
|
2022-01-14 17:08:17 +03:00
|
|
|
import Database.MSSQL.Pool qualified as MSPool
|
|
|
|
import Database.MSSQL.Transaction qualified as MSTx
|
2021-02-25 21:15:55 +03:00
|
|
|
import Database.ODBC.SQLServer qualified as ODBC
|
2022-02-07 17:11:49 +03:00
|
|
|
import Hasura.Backends.MSSQL.SQL.Error
|
2021-05-11 18:18:31 +03:00
|
|
|
import Hasura.Base.Error
|
2022-10-12 19:28:51 +03:00
|
|
|
import Hasura.Metadata.DTO.Utils (fromEnvCodec)
|
2021-02-23 20:37:27 +03:00
|
|
|
import Hasura.Prelude
|
2023-03-15 13:29:13 +03:00
|
|
|
import Hasura.RQL.Types.ResizePool
|
2021-09-09 13:37:50 +03:00
|
|
|
|
2022-02-24 11:13:19 +03:00
|
|
|
class MonadError QErr m => MonadMSSQLTx m where
|
|
|
|
liftMSSQLTx :: MSTx.TxE QErr a -> m a
|
|
|
|
|
|
|
|
instance MonadMSSQLTx m => MonadMSSQLTx (ReaderT s m) where
|
|
|
|
liftMSSQLTx = lift . liftMSSQLTx
|
|
|
|
|
|
|
|
instance MonadMSSQLTx m => MonadMSSQLTx (StateT s m) where
|
|
|
|
liftMSSQLTx = lift . liftMSSQLTx
|
|
|
|
|
|
|
|
instance (Monoid w, MonadMSSQLTx m) => MonadMSSQLTx (WriterT w m) where
|
|
|
|
liftMSSQLTx = lift . liftMSSQLTx
|
|
|
|
|
|
|
|
instance MonadIO m => MonadMSSQLTx (MSTx.TxET QErr m) where
|
|
|
|
liftMSSQLTx = hoist liftIO
|
|
|
|
|
|
|
|
-- | ODBC connection string for MSSQL server
|
|
|
|
newtype MSSQLConnectionString = MSSQLConnectionString {unMSSQLConnectionString :: Text}
|
server: delete the `Cacheable` type class in favor of `Eq`
What is the `Cacheable` type class about?
```haskell
class Eq a => Cacheable a where
unchanged :: Accesses -> a -> a -> Bool
default unchanged :: (Generic a, GCacheable (Rep a)) => Accesses -> a -> a -> Bool
unchanged accesses a b = gunchanged (from a) (from b) accesses
```
Its only method is an alternative to `(==)`. The added value of `unchanged` (and the additional `Accesses` argument) arises _only_ for one type, namely `Dependency`. Indeed, the `Cacheable (Dependency a)` instance is non-trivial, whereas every other `Cacheable` instance is completely boilerplate (and indeed either generated from `Generic`, or simply `unchanged _ = (==)`). The `Cacheable (Dependency a)` instance is the only one where the `Accesses` argument is not just passed onwards.
The only callsite of the `unchanged` method is in the `ArrowCache (Rule m)` method. That is to say that the `Cacheable` type class is used to decide when we can re-use parts of the schema cache between Metadata operations.
So what is the `Cacheable (Dependency a)` instance about? Normally, the output of a `Rule m a b` is re-used when the new input (of type `a`) is equal to the old one. But sometimes, that's too coarse: it might be that a certain `Rule m a b` only depends on a small part of its input of type `a`. A `Dependency` allows us to spell out what parts of `a` are being depended on, and these parts are recorded as values of types `Access a` in the state `Accesses`.
If the input `a` changes, but not in a way that touches the recorded `Accesses`, then the output `b` of that rule can be re-used without recomputing.
So now you understand _why_ we're passing `Accesses` to the `unchanged` method: `unchanged` is an equality check in disguise that just needs some additional context.
But we don't need to pass `Accesses` as a function argument. We can use the `reflection` package to pass it as type-level context. So the core of this PR is that we change the instance declaration from
```haskell
instance (Cacheable a) => Cacheable (Dependency a) where
```
to
```haskell
instance (Given Accesses, Eq a) => Eq (Dependency a) where
```
and use `(==)` instead of `unchanged`.
If you haven't seen `reflection` before: it's like a `MonadReader`, but it doesn't require a `Monad`.
In order to pass the current `Accesses` value, instead of simply passing the `Accesses` as a function argument, we need to instantiate the `Given Accesses` context. We use the `give` method from the `reflection` package for that.
```haskell
give :: forall r. Accesses -> (Given Accesses => r) -> r
unchanged :: (Given Accesses => Eq a) => Accesses -> a -> a -> Bool
unchanged accesses a b = give accesses (a == b)
```
With these three components in place, we can delete the `Cacheable` type class entirely.
The remainder of this PR is just to remove the `Cacheable` type class and its instances.
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/6877
GitOrigin-RevId: 7125f5e11d856e7672ab810a23d5bf5ad176e77f
2022-11-21 19:33:56 +03:00
|
|
|
deriving (Show, Eq, ToJSON, FromJSON, Hashable, NFData)
|
2022-02-24 11:13:19 +03:00
|
|
|
|
2022-01-14 17:08:17 +03:00
|
|
|
-- * Orphan instances
|
|
|
|
|
|
|
|
instance Hashable MSPool.ConnectionString
|
|
|
|
|
|
|
|
instance NFData MSPool.ConnectionString
|
2021-02-23 20:37:27 +03:00
|
|
|
|
2021-03-18 21:32:47 +03:00
|
|
|
data InputConnectionString
|
2022-07-29 17:05:03 +03:00
|
|
|
= RawString MSPool.ConnectionString
|
|
|
|
| FromEnvironment Text
|
2021-03-18 21:32:47 +03:00
|
|
|
deriving stock (Show, Eq, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-03-18 21:32:47 +03:00
|
|
|
instance Hashable InputConnectionString
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-03-18 21:32:47 +03:00
|
|
|
instance NFData InputConnectionString
|
|
|
|
|
2022-10-12 19:28:51 +03:00
|
|
|
instance HasCodec InputConnectionString where
|
|
|
|
codec =
|
|
|
|
dimapCodec
|
|
|
|
(either RawString FromEnvironment)
|
|
|
|
(\case RawString m -> Left m; FromEnvironment wEnv -> Right wEnv)
|
|
|
|
$ disjointEitherCodec codec fromEnvCodec
|
|
|
|
|
2021-03-18 21:32:47 +03:00
|
|
|
instance ToJSON InputConnectionString where
|
|
|
|
toJSON =
|
|
|
|
\case
|
|
|
|
(RawString m) -> toJSON m
|
|
|
|
(FromEnvironment wEnv) -> object ["from_env" .= wEnv]
|
|
|
|
|
|
|
|
instance FromJSON InputConnectionString where
|
|
|
|
parseJSON =
|
|
|
|
\case
|
|
|
|
(Object o) -> FromEnvironment <$> o .: "from_env"
|
|
|
|
s@(String _) -> RawString <$> parseJSON s
|
|
|
|
_ -> fail "one of string or object must be provided"
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-25 21:15:55 +03:00
|
|
|
data MSSQLPoolSettings = MSSQLPoolSettings
|
2022-10-17 11:04:54 +03:00
|
|
|
{ _mpsMaxConnections :: Maybe Int,
|
|
|
|
_mpsTotalMaxConnections :: Maybe Int,
|
2022-07-29 17:05:03 +03:00
|
|
|
_mpsIdleTimeout :: Int
|
2021-09-24 01:56:37 +03:00
|
|
|
}
|
2021-02-25 21:15:55 +03:00
|
|
|
deriving (Show, Eq, Generic)
|
2021-03-18 21:32:47 +03:00
|
|
|
|
2021-02-25 21:15:55 +03:00
|
|
|
instance Hashable MSSQLPoolSettings
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-25 21:15:55 +03:00
|
|
|
instance NFData MSSQLPoolSettings
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-25 21:15:55 +03:00
|
|
|
$(deriveToJSON hasuraJSON ''MSSQLPoolSettings)
|
|
|
|
|
|
|
|
instance FromJSON MSSQLPoolSettings where
|
|
|
|
parseJSON = withObject "MSSQL pool settings" $ \o ->
|
|
|
|
MSSQLPoolSettings
|
2022-10-17 11:04:54 +03:00
|
|
|
<$> o .:? "max_connections"
|
|
|
|
<*> o .:? "total_max_connections"
|
2021-02-25 21:15:55 +03:00
|
|
|
<*> o .:? "idle_timeout" .!= _mpsIdleTimeout defaultMSSQLPoolSettings
|
|
|
|
|
2022-10-12 19:28:51 +03:00
|
|
|
instance HasCodec MSSQLPoolSettings where
|
|
|
|
codec =
|
|
|
|
AC.object "MSSQLPoolSettings" $
|
|
|
|
MSSQLPoolSettings
|
2022-10-17 11:04:54 +03:00
|
|
|
<$> optionalFieldWithDefault' "max_connections" (Just defaultMSSQLMaxConnections) AC..= _mpsMaxConnections
|
|
|
|
<*> optionalFieldOrNull' "total_max_connections" AC..= _mpsTotalMaxConnections
|
|
|
|
<*> optionalFieldWithDefault' "idle_timeout" (_mpsIdleTimeout defaultMSSQLPoolSettings) AC..= _mpsIdleTimeout
|
|
|
|
|
|
|
|
defaultMSSQLMaxConnections :: Int
|
|
|
|
defaultMSSQLMaxConnections = 50
|
2022-10-12 19:28:51 +03:00
|
|
|
|
2021-02-25 21:15:55 +03:00
|
|
|
defaultMSSQLPoolSettings :: MSSQLPoolSettings
|
|
|
|
defaultMSSQLPoolSettings =
|
|
|
|
MSSQLPoolSettings
|
2022-10-17 11:04:54 +03:00
|
|
|
{ _mpsMaxConnections = Nothing,
|
|
|
|
_mpsTotalMaxConnections = Nothing,
|
2021-02-25 21:15:55 +03:00
|
|
|
_mpsIdleTimeout = 5
|
2021-09-24 01:56:37 +03:00
|
|
|
}
|
|
|
|
|
2021-07-23 15:25:16 +03:00
|
|
|
data MSSQLConnectionInfo = MSSQLConnectionInfo
|
2022-07-29 17:05:03 +03:00
|
|
|
{ _mciConnectionString :: InputConnectionString,
|
|
|
|
_mciPoolSettings :: MSSQLPoolSettings
|
2021-02-25 21:15:55 +03:00
|
|
|
}
|
2021-02-23 20:37:27 +03:00
|
|
|
deriving (Show, Eq, Generic)
|
2021-02-25 21:15:55 +03:00
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
instance Hashable MSSQLConnectionInfo
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
instance NFData MSSQLConnectionInfo
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2022-10-12 19:28:51 +03:00
|
|
|
instance HasCodec MSSQLConnectionInfo where
|
|
|
|
codec =
|
|
|
|
AC.object "MSSQLConnectionInfo" $
|
|
|
|
MSSQLConnectionInfo
|
|
|
|
<$> requiredField' "connection_string" AC..= _mciConnectionString
|
|
|
|
<*> requiredField' "pool_settings" AC..= _mciPoolSettings
|
|
|
|
|
2021-02-25 21:15:55 +03:00
|
|
|
$(deriveToJSON hasuraJSON ''MSSQLConnectionInfo)
|
|
|
|
|
|
|
|
instance FromJSON MSSQLConnectionInfo where
|
|
|
|
parseJSON = withObject "Object" $ \o ->
|
|
|
|
MSSQLConnectionInfo
|
|
|
|
<$> ((o .: "database_url") <|> (o .: "connection_string"))
|
|
|
|
<*> o .:? "pool_settings" .!= defaultMSSQLPoolSettings
|
2021-02-23 20:37:27 +03:00
|
|
|
|
|
|
|
data MSSQLConnConfiguration = MSSQLConnConfiguration
|
2022-07-29 17:05:03 +03:00
|
|
|
{ _mccConnectionInfo :: MSSQLConnectionInfo,
|
|
|
|
_mccReadReplicas :: Maybe (NonEmpty MSSQLConnectionInfo)
|
2021-02-23 20:37:27 +03:00
|
|
|
}
|
|
|
|
deriving (Show, Eq, Generic)
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
instance Hashable MSSQLConnConfiguration
|
2021-09-24 01:56:37 +03:00
|
|
|
|
2021-02-23 20:37:27 +03:00
|
|
|
instance NFData MSSQLConnConfiguration
|
2021-09-24 01:56:37 +03:00
|
|
|
|
server: polymorphic codec for metadata sources
This PR expands the OpenAPI specification generated for metadata to include separate definitions for `SourceMetadata` for each native database type, and for DataConnector.
For the most part the changes add `HasCodec` implementations, and don't modify existing code otherwise.
The generated OpenAPI spec can be used to generate TypeScript definitions that distinguish different source metadata types based on the value of the `kind` properly. There is a problem: because the specified `kind` value for a data connector source is any string, when TypeScript gets a source with a `kind` value of, say, `"postgres"`, it cannot unambiguously determine whether the source is postgres, or a data connector. For example,
```ts
function consumeSourceMetadata(source: SourceMetadata) {
if (source.kind === "postgres" || source.kind === "pg") {
// At this point TypeScript infers that `source` is either an instance
// of `PostgresSourceMetadata`, or `DataconnectorSourceMetadata`. It
// can't narrow further.
source
}
if (source.kind === "something else") {
// TypeScript infers that this `source` must be an instance of
// `DataconnectorSourceMetadata` because `source.kind` does not match
// any of the other options.
source
}
}
```
The simplest way I can think of to fix this would be to add a boolean property to the `SourceMetadata` type along the lines of `isNative` or `isDataConnector`. This could be a field that only exists in serialized data, like the metadata version field. The combination of one of the native database names for `kind`, and a true value for `isNative` would be enough for TypeScript to unambiguously distinguish the source kinds.
But note that in the current state TypeScript is able to reference the short `"pg"` name correctly!
~~Tests are not passing yet due to some discrepancies in DTO serialization vs existing Metadata serialization. I'm working on that.~~
The placeholders that I used for table and function metadata are not compatible with the ordered JSON serialization in use. I think the best solution is to write compatible codecs for those types in another PR. For now I have disabled some DTO tests for this PR.
Here are the generated [OpenAPI spec](https://github.com/hasura/graphql-engine-mono/files/9397333/openapi.tar.gz) based on these changes, and the generated [TypeScript client code](https://github.com/hasura/graphql-engine-mono/files/9397339/client-typescript.tar.gz) based on that spec.
Ticket: [MM-66](https://hasurahq.atlassian.net/browse/MM-66)
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5582
GitOrigin-RevId: e1446191c6c832879db04f129daa397a3be03f62
2022-08-25 21:34:44 +03:00
|
|
|
instance HasCodec MSSQLConnConfiguration where
|
2022-10-12 19:28:51 +03:00
|
|
|
codec =
|
|
|
|
AC.object "MSSQLConnConfiguration" $
|
|
|
|
MSSQLConnConfiguration
|
|
|
|
<$> requiredField' "connection_info" AC..= _mccConnectionInfo
|
|
|
|
<*> optionalFieldOrNull' "read_replicas" AC..= _mccReadReplicas
|
|
|
|
|
|
|
|
$(deriveJSON hasuraJSON {omitNothingFields = True} ''MSSQLConnConfiguration)
|
server: polymorphic codec for metadata sources
This PR expands the OpenAPI specification generated for metadata to include separate definitions for `SourceMetadata` for each native database type, and for DataConnector.
For the most part the changes add `HasCodec` implementations, and don't modify existing code otherwise.
The generated OpenAPI spec can be used to generate TypeScript definitions that distinguish different source metadata types based on the value of the `kind` properly. There is a problem: because the specified `kind` value for a data connector source is any string, when TypeScript gets a source with a `kind` value of, say, `"postgres"`, it cannot unambiguously determine whether the source is postgres, or a data connector. For example,
```ts
function consumeSourceMetadata(source: SourceMetadata) {
if (source.kind === "postgres" || source.kind === "pg") {
// At this point TypeScript infers that `source` is either an instance
// of `PostgresSourceMetadata`, or `DataconnectorSourceMetadata`. It
// can't narrow further.
source
}
if (source.kind === "something else") {
// TypeScript infers that this `source` must be an instance of
// `DataconnectorSourceMetadata` because `source.kind` does not match
// any of the other options.
source
}
}
```
The simplest way I can think of to fix this would be to add a boolean property to the `SourceMetadata` type along the lines of `isNative` or `isDataConnector`. This could be a field that only exists in serialized data, like the metadata version field. The combination of one of the native database names for `kind`, and a true value for `isNative` would be enough for TypeScript to unambiguously distinguish the source kinds.
But note that in the current state TypeScript is able to reference the short `"pg"` name correctly!
~~Tests are not passing yet due to some discrepancies in DTO serialization vs existing Metadata serialization. I'm working on that.~~
The placeholders that I used for table and function metadata are not compatible with the ordered JSON serialization in use. I think the best solution is to write compatible codecs for those types in another PR. For now I have disabled some DTO tests for this PR.
Here are the generated [OpenAPI spec](https://github.com/hasura/graphql-engine-mono/files/9397333/openapi.tar.gz) based on these changes, and the generated [TypeScript client code](https://github.com/hasura/graphql-engine-mono/files/9397339/client-typescript.tar.gz) based on that spec.
Ticket: [MM-66](https://hasurahq.atlassian.net/browse/MM-66)
PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5582
GitOrigin-RevId: e1446191c6c832879db04f129daa397a3be03f62
2022-08-25 21:34:44 +03:00
|
|
|
|
2021-03-18 21:32:47 +03:00
|
|
|
createMSSQLPool ::
|
|
|
|
MonadIO m =>
|
|
|
|
QErrM m =>
|
2022-10-17 11:04:54 +03:00
|
|
|
InputConnectionString ->
|
|
|
|
MSPool.ConnectionOptions ->
|
2021-07-23 15:25:16 +03:00
|
|
|
Env.Environment ->
|
2022-01-14 17:08:17 +03:00
|
|
|
m (MSPool.ConnectionString, MSPool.MSSQLPool)
|
2022-10-17 11:04:54 +03:00
|
|
|
createMSSQLPool iConnString connOptions env = do
|
2021-03-18 21:32:47 +03:00
|
|
|
connString <- resolveInputConnectionString env iConnString
|
2022-01-14 17:08:17 +03:00
|
|
|
pool <- liftIO $ MSPool.initMSSQLPool connString connOptions
|
2021-03-18 21:32:47 +03:00
|
|
|
pure (connString, pool)
|
|
|
|
|
|
|
|
resolveInputConnectionString ::
|
|
|
|
QErrM m =>
|
|
|
|
Env.Environment ->
|
|
|
|
InputConnectionString ->
|
2022-01-14 17:08:17 +03:00
|
|
|
m MSPool.ConnectionString
|
2021-03-18 21:32:47 +03:00
|
|
|
resolveInputConnectionString env =
|
|
|
|
\case
|
|
|
|
(RawString cs) -> pure cs
|
2022-01-14 17:08:17 +03:00
|
|
|
(FromEnvironment envVar) -> MSPool.ConnectionString <$> getEnv env envVar
|
2021-03-18 21:32:47 +03:00
|
|
|
|
|
|
|
getEnv :: QErrM m => Env.Environment -> Text -> m Text
|
|
|
|
getEnv env k = do
|
|
|
|
let mEnv = Env.lookupEnv env (unpack k)
|
|
|
|
case mEnv of
|
|
|
|
Nothing -> throw400 NotFound $ "environment variable '" <> k <> "' not set"
|
|
|
|
Just envVal -> return (pack envVal)
|
2021-02-25 21:15:55 +03:00
|
|
|
|
2022-01-04 14:53:50 +03:00
|
|
|
type MSSQLRunTx =
|
2022-01-14 17:08:17 +03:00
|
|
|
forall m a. (MonadIO m, MonadBaseControl IO m) => MSTx.TxET QErr m a -> ExceptT QErr m a
|
2022-01-04 14:53:50 +03:00
|
|
|
|
|
|
|
-- | Execution Context required to execute MSSQL transactions
|
|
|
|
data MSSQLExecCtx = MSSQLExecCtx
|
|
|
|
{ -- | A function that runs read-only queries
|
2022-01-14 17:08:17 +03:00
|
|
|
mssqlRunReadOnly :: MSSQLRunTx,
|
|
|
|
-- | A function that runs read-write queries; run in a transaction
|
|
|
|
mssqlRunReadWrite :: MSSQLRunTx,
|
2022-11-02 01:41:22 +03:00
|
|
|
-- | A function that runs a transaction in the SERIALIZABLE transaction isolation
|
|
|
|
-- level. This is mainly intended to run source catalog migrations.
|
|
|
|
mssqlRunSerializableTx :: MSSQLRunTx,
|
2022-01-04 14:53:50 +03:00
|
|
|
-- | Destroys connection pools
|
2022-10-17 11:04:54 +03:00
|
|
|
mssqlDestroyConn :: IO (),
|
2023-03-15 13:29:13 +03:00
|
|
|
-- | Resize pools based on number of server instances
|
|
|
|
mssqlResizePools :: ServerReplicas -> IO SourceResizePoolSummary
|
2022-01-04 14:53:50 +03:00
|
|
|
}
|
|
|
|
|
|
|
|
-- | Creates a MSSQL execution context for a single primary pool
|
2022-10-17 11:04:54 +03:00
|
|
|
mkMSSQLExecCtx :: MSPool.MSSQLPool -> ResizePoolStrategy -> MSSQLExecCtx
|
|
|
|
mkMSSQLExecCtx pool resizeStrategy =
|
2022-01-04 14:53:50 +03:00
|
|
|
MSSQLExecCtx
|
2022-11-02 01:41:22 +03:00
|
|
|
{ mssqlRunReadOnly = \tx -> MSTx.runTxE defaultMSSQLTxErrorHandler MSTx.ReadCommitted tx pool,
|
|
|
|
mssqlRunReadWrite = \tx -> MSTx.runTxE defaultMSSQLTxErrorHandler MSTx.ReadCommitted tx pool,
|
|
|
|
mssqlRunSerializableTx = \tx -> MSTx.runTxE defaultMSSQLTxErrorHandler MSTx.Serializable tx pool,
|
2022-10-17 11:04:54 +03:00
|
|
|
mssqlDestroyConn = MSPool.drainMSSQLPool pool,
|
|
|
|
mssqlResizePools =
|
|
|
|
case resizeStrategy of
|
2023-03-15 13:29:13 +03:00
|
|
|
NeverResizePool -> const $ pure noPoolsResizedSummary
|
|
|
|
ResizePool maxConnections -> resizeMSSQLPool' maxConnections
|
2022-01-04 14:53:50 +03:00
|
|
|
}
|
2023-03-15 13:29:13 +03:00
|
|
|
where
|
|
|
|
resizeMSSQLPool' maxConnections serverReplicas = do
|
|
|
|
-- Resize the primary pool
|
|
|
|
resizeMSSQLPool pool maxConnections serverReplicas
|
|
|
|
-- Return the summary. Only the primary pool is resized
|
|
|
|
pure $
|
|
|
|
SourceResizePoolSummary
|
|
|
|
{ _srpsPrimaryResized = True,
|
|
|
|
_srpsReadReplicasResized = False,
|
|
|
|
_srpsConnectionSet = []
|
|
|
|
}
|
2022-01-04 14:53:50 +03:00
|
|
|
|
2022-10-17 11:04:54 +03:00
|
|
|
-- | Resize MSSQL pool by setting the number of connections equal to
|
|
|
|
-- allowed maximum connections across all server instances divided by
|
|
|
|
-- number of instances
|
|
|
|
resizeMSSQLPool :: MSPool.MSSQLPool -> Int -> ServerReplicas -> IO ()
|
|
|
|
resizeMSSQLPool mssqlPool maxConnections serverReplicas =
|
|
|
|
MSPool.resizePool mssqlPool (maxConnections `div` getServerReplicasInt serverReplicas)
|
|
|
|
|
2022-09-02 09:33:21 +03:00
|
|
|
-- | Run any query discarding its results
|
|
|
|
mkMSSQLAnyQueryTx :: ODBC.Query -> MSTx.TxET QErr IO ()
|
|
|
|
mkMSSQLAnyQueryTx q = do
|
|
|
|
_discard :: [[ODBC.Value]] <- MSTx.multiRowQueryE defaultMSSQLTxErrorHandler q
|
|
|
|
pure ()
|
|
|
|
|
2021-02-25 21:15:55 +03:00
|
|
|
data MSSQLSourceConfig = MSSQLSourceConfig
|
2022-07-29 17:05:03 +03:00
|
|
|
{ _mscConnectionString :: MSPool.ConnectionString,
|
2023-04-05 11:57:19 +03:00
|
|
|
_mscExecCtx :: MSSQLExecCtx,
|
|
|
|
-- | Number of read replicas used by the execution context
|
|
|
|
_mscReadReplicas :: Int
|
2021-02-25 21:15:55 +03:00
|
|
|
}
|
|
|
|
deriving (Generic)
|
|
|
|
|
|
|
|
instance Show MSSQLSourceConfig where
|
|
|
|
show = show . _mscConnectionString
|
|
|
|
|
|
|
|
instance Eq MSSQLSourceConfig where
|
2023-04-05 11:57:19 +03:00
|
|
|
MSSQLSourceConfig connStr1 _ _ == MSSQLSourceConfig connStr2 _ _ =
|
2021-02-25 21:15:55 +03:00
|
|
|
connStr1 == connStr2
|
|
|
|
|
|
|
|
instance ToJSON MSSQLSourceConfig where
|
|
|
|
toJSON = toJSON . _mscConnectionString
|
2021-09-09 10:59:04 +03:00
|
|
|
|
2021-10-01 15:52:19 +03:00
|
|
|
odbcValueToJValue :: ODBC.Value -> J.Value
|
|
|
|
odbcValueToJValue = \case
|
|
|
|
ODBC.TextValue t -> J.String t
|
|
|
|
ODBC.ByteStringValue b -> J.String $ bsToTxt b
|
|
|
|
ODBC.BinaryValue b -> J.String $ bsToTxt $ ODBC.unBinary b
|
|
|
|
ODBC.BoolValue b -> J.Bool b
|
|
|
|
ODBC.DoubleValue d -> J.toJSON d
|
|
|
|
ODBC.FloatValue f -> J.toJSON f
|
|
|
|
ODBC.IntValue i -> J.toJSON i
|
|
|
|
ODBC.ByteValue b -> J.toJSON b
|
|
|
|
ODBC.DayValue d -> J.toJSON d
|
|
|
|
ODBC.TimeOfDayValue td -> J.toJSON td
|
|
|
|
ODBC.LocalTimeValue l -> J.toJSON l
|
|
|
|
ODBC.NullValue -> J.Null
|
2022-09-13 11:33:44 +03:00
|
|
|
ODBC.ZonedTimeValue lt tz -> J.toJSON (localTimeToUTC tz lt)
|
2022-04-21 10:19:37 +03:00
|
|
|
|
|
|
|
runMSSQLSourceReadTx ::
|
|
|
|
(MonadIO m, MonadBaseControl IO m) =>
|
|
|
|
MSSQLSourceConfig ->
|
|
|
|
MSTx.TxET QErr m a ->
|
|
|
|
m (Either QErr a)
|
|
|
|
runMSSQLSourceReadTx msc =
|
|
|
|
runExceptT . mssqlRunReadOnly (_mscExecCtx msc)
|
|
|
|
|
|
|
|
runMSSQLSourceWriteTx ::
|
|
|
|
(MonadIO m, MonadBaseControl IO m) =>
|
|
|
|
MSSQLSourceConfig ->
|
|
|
|
MSTx.TxET QErr m a ->
|
|
|
|
m (Either QErr a)
|
|
|
|
runMSSQLSourceWriteTx msc =
|
|
|
|
runExceptT . mssqlRunReadWrite (_mscExecCtx msc)
|