{-# LANGUAGE UndecidableInstances #-}
module Hasura.StoredProcedure.API
( GetStoredProcedure (..),
TrackStoredProcedure (..),
UntrackStoredProcedure (..),
runGetStoredProcedure,
runTrackStoredProcedure,
runUntrackStoredProcedure,
dropStoredProcedureInMetadata,
module Hasura.StoredProcedure.Types,
)
where
import Autodocodec (HasCodec)
import Autodocodec qualified as AC
import Control.Lens (Traversal', has, preview, (^?))
import Data.Aeson
import Data.HashMap.Strict.InsOrd.Extended qualified as InsOrdHashMap
import Data.Text.Extended (toTxt, (<<>))
import Hasura.Base.Error
import Hasura.EncJSON
import Hasura.LogicalModel.Metadata (LogicalModelName)
import Hasura.Prelude
import Hasura.RQL.Types.Backend (Backend, FunctionName)
import Hasura.RQL.Types.BackendTag
import Hasura.RQL.Types.BackendType
import Hasura.RQL.Types.Common
( SourceName,
sourceNameToText,
successMsg,
)
import Hasura.RQL.Types.Metadata
import Hasura.RQL.Types.Metadata.Backend
import Hasura.RQL.Types.Metadata.Object
import Hasura.RQL.Types.SchemaCache.Build
import Hasura.SQL.AnyBackend qualified as AB
import Hasura.StoredProcedure.Metadata (ArgumentName, StoredProcedureMetadata (..))
import Hasura.StoredProcedure.Types
data TrackStoredProcedure (b :: BackendType) = TrackStoredProcedure
{ forall (b :: BackendType). TrackStoredProcedure b -> SourceName
tspSource :: SourceName,
forall (b :: BackendType). TrackStoredProcedure b -> FunctionName b
tspStoredProcedure :: FunctionName b,
forall (b :: BackendType).
TrackStoredProcedure b -> StoredProcedureConfig
tspConfig :: StoredProcedureConfig,
forall (b :: BackendType).
TrackStoredProcedure b
-> HashMap ArgumentName (NullableScalarType b)
tspArguments :: HashMap ArgumentName (NullableScalarType b),
forall (b :: BackendType). TrackStoredProcedure b -> Maybe Text
tspDescription :: Maybe Text,
forall (b :: BackendType).
TrackStoredProcedure b -> LogicalModelName
tspReturns :: LogicalModelName
}
instance (Backend b) => HasCodec (TrackStoredProcedure b) where
codec :: JSONCodec (TrackStoredProcedure b)
codec =
Text
-> JSONCodec (TrackStoredProcedure b)
-> JSONCodec (TrackStoredProcedure b)
forall input output.
Text -> ValueCodec input output -> ValueCodec input output
AC.CommentCodec
(Text
"A request to track a stored procedure")
(JSONCodec (TrackStoredProcedure b)
-> JSONCodec (TrackStoredProcedure b))
-> JSONCodec (TrackStoredProcedure b)
-> JSONCodec (TrackStoredProcedure b)
forall a b. (a -> b) -> a -> b
$ Text
-> ObjectCodec (TrackStoredProcedure b) (TrackStoredProcedure b)
-> JSONCodec (TrackStoredProcedure b)
forall input output.
Text -> ObjectCodec input output -> ValueCodec input output
AC.object (forall (b :: BackendType). HasTag b => Text
backendPrefix @b Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"TrackStoredProcedure")
(ObjectCodec (TrackStoredProcedure b) (TrackStoredProcedure b)
-> JSONCodec (TrackStoredProcedure b))
-> ObjectCodec (TrackStoredProcedure b) (TrackStoredProcedure b)
-> JSONCodec (TrackStoredProcedure b)
forall a b. (a -> b) -> a -> b
$ SourceName
-> FunctionName b
-> StoredProcedureConfig
-> HashMap ArgumentName (NullableScalarType b)
-> Maybe Text
-> LogicalModelName
-> TrackStoredProcedure b
forall (b :: BackendType).
SourceName
-> FunctionName b
-> StoredProcedureConfig
-> HashMap ArgumentName (NullableScalarType b)
-> Maybe Text
-> LogicalModelName
-> TrackStoredProcedure b
TrackStoredProcedure
(SourceName
-> FunctionName b
-> StoredProcedureConfig
-> HashMap ArgumentName (NullableScalarType b)
-> Maybe Text
-> LogicalModelName
-> TrackStoredProcedure b)
-> Codec Object (TrackStoredProcedure b) SourceName
-> Codec
Object
(TrackStoredProcedure b)
(FunctionName b
-> StoredProcedureConfig
-> HashMap ArgumentName (NullableScalarType b)
-> Maybe Text
-> LogicalModelName
-> TrackStoredProcedure b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> ObjectCodec SourceName SourceName
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
AC.requiredField Text
"source" Text
sourceDoc
ObjectCodec SourceName SourceName
-> (TrackStoredProcedure b -> SourceName)
-> Codec Object (TrackStoredProcedure b) SourceName
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackStoredProcedure b -> SourceName
forall (b :: BackendType). TrackStoredProcedure b -> SourceName
tspSource
Codec
Object
(TrackStoredProcedure b)
(FunctionName b
-> StoredProcedureConfig
-> HashMap ArgumentName (NullableScalarType b)
-> Maybe Text
-> LogicalModelName
-> TrackStoredProcedure b)
-> Codec Object (TrackStoredProcedure b) (FunctionName b)
-> Codec
Object
(TrackStoredProcedure b)
(StoredProcedureConfig
-> HashMap ArgumentName (NullableScalarType b)
-> Maybe Text
-> LogicalModelName
-> TrackStoredProcedure b)
forall a b.
Codec Object (TrackStoredProcedure b) (a -> b)
-> Codec Object (TrackStoredProcedure b) a
-> Codec Object (TrackStoredProcedure b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (FunctionName b) (FunctionName b)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
AC.requiredField Text
"stored_procedure" Text
spDoc
ObjectCodec (FunctionName b) (FunctionName b)
-> (TrackStoredProcedure b -> FunctionName b)
-> Codec Object (TrackStoredProcedure b) (FunctionName b)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackStoredProcedure b -> FunctionName b
forall (b :: BackendType). TrackStoredProcedure b -> FunctionName b
tspStoredProcedure
Codec
Object
(TrackStoredProcedure b)
(StoredProcedureConfig
-> HashMap ArgumentName (NullableScalarType b)
-> Maybe Text
-> LogicalModelName
-> TrackStoredProcedure b)
-> Codec Object (TrackStoredProcedure b) StoredProcedureConfig
-> Codec
Object
(TrackStoredProcedure b)
(HashMap ArgumentName (NullableScalarType b)
-> Maybe Text -> LogicalModelName -> TrackStoredProcedure b)
forall a b.
Codec Object (TrackStoredProcedure b) (a -> b)
-> Codec Object (TrackStoredProcedure b) a
-> Codec Object (TrackStoredProcedure b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> Text -> ObjectCodec StoredProcedureConfig StoredProcedureConfig
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
AC.requiredField Text
"configuration" Text
configDoc
ObjectCodec StoredProcedureConfig StoredProcedureConfig
-> (TrackStoredProcedure b -> StoredProcedureConfig)
-> Codec Object (TrackStoredProcedure b) StoredProcedureConfig
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackStoredProcedure b -> StoredProcedureConfig
forall (b :: BackendType).
TrackStoredProcedure b -> StoredProcedureConfig
tspConfig
Codec
Object
(TrackStoredProcedure b)
(HashMap ArgumentName (NullableScalarType b)
-> Maybe Text -> LogicalModelName -> TrackStoredProcedure b)
-> Codec
Object
(TrackStoredProcedure b)
(HashMap ArgumentName (NullableScalarType b))
-> Codec
Object
(TrackStoredProcedure b)
(Maybe Text -> LogicalModelName -> TrackStoredProcedure b)
forall a b.
Codec Object (TrackStoredProcedure b) (a -> b)
-> Codec Object (TrackStoredProcedure b) a
-> Codec Object (TrackStoredProcedure b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text
-> HashMap ArgumentName (NullableScalarType b)
-> Text
-> ObjectCodec
(HashMap ArgumentName (NullableScalarType b))
(HashMap ArgumentName (NullableScalarType b))
forall output.
HasCodec output =>
Text -> output -> Text -> ObjectCodec output output
AC.optionalFieldWithDefault Text
"arguments" HashMap ArgumentName (NullableScalarType b)
forall a. Monoid a => a
mempty Text
argumentsDoc
ObjectCodec
(HashMap ArgumentName (NullableScalarType b))
(HashMap ArgumentName (NullableScalarType b))
-> (TrackStoredProcedure b
-> HashMap ArgumentName (NullableScalarType b))
-> Codec
Object
(TrackStoredProcedure b)
(HashMap ArgumentName (NullableScalarType b))
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackStoredProcedure b
-> HashMap ArgumentName (NullableScalarType b)
forall (b :: BackendType).
TrackStoredProcedure b
-> HashMap ArgumentName (NullableScalarType b)
tspArguments
Codec
Object
(TrackStoredProcedure b)
(Maybe Text -> LogicalModelName -> TrackStoredProcedure b)
-> Codec Object (TrackStoredProcedure b) (Maybe Text)
-> Codec
Object
(TrackStoredProcedure b)
(LogicalModelName -> TrackStoredProcedure b)
forall a b.
Codec Object (TrackStoredProcedure b) (a -> b)
-> Codec Object (TrackStoredProcedure b) a
-> Codec Object (TrackStoredProcedure b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec (Maybe Text) (Maybe Text)
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec (Maybe output) (Maybe output)
AC.optionalField Text
"description" Text
descriptionDoc
ObjectCodec (Maybe Text) (Maybe Text)
-> (TrackStoredProcedure b -> Maybe Text)
-> Codec Object (TrackStoredProcedure b) (Maybe Text)
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackStoredProcedure b -> Maybe Text
forall (b :: BackendType). TrackStoredProcedure b -> Maybe Text
tspDescription
Codec
Object
(TrackStoredProcedure b)
(LogicalModelName -> TrackStoredProcedure b)
-> Codec Object (TrackStoredProcedure b) LogicalModelName
-> ObjectCodec (TrackStoredProcedure b) (TrackStoredProcedure b)
forall a b.
Codec Object (TrackStoredProcedure b) (a -> b)
-> Codec Object (TrackStoredProcedure b) a
-> Codec Object (TrackStoredProcedure b) b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Text -> Text -> ObjectCodec LogicalModelName LogicalModelName
forall output.
HasCodec output =>
Text -> Text -> ObjectCodec output output
AC.requiredField Text
"returns" Text
returnsDoc
ObjectCodec LogicalModelName LogicalModelName
-> (TrackStoredProcedure b -> LogicalModelName)
-> Codec Object (TrackStoredProcedure b) LogicalModelName
forall oldInput output newInput.
ObjectCodec oldInput output
-> (newInput -> oldInput) -> ObjectCodec newInput output
AC..= TrackStoredProcedure b -> LogicalModelName
forall (b :: BackendType).
TrackStoredProcedure b -> LogicalModelName
tspReturns
where
sourceDoc :: Text
sourceDoc = Text
"The source in which this stored procedure should be tracked"
configDoc :: Text
configDoc = Text
"The configuration for the SQL stored procedure"
spDoc :: Text
spDoc = Text
"The name of the SQL stored procedure"
argumentsDoc :: Text
argumentsDoc = Text
"Free variables in the expression and their types"
returnsDoc :: Text
returnsDoc = Text
"Return type (table) of the expression"
descriptionDoc :: Text
descriptionDoc = Text
"A description of the query which appears in the graphql schema"
deriving via
(AC.Autodocodec (TrackStoredProcedure b))
instance
(Backend b) => FromJSON (TrackStoredProcedure b)
deriving via
(AC.Autodocodec (TrackStoredProcedure b))
instance
(Backend b) => ToJSON (TrackStoredProcedure b)
data GetStoredProcedure (b :: BackendType) = GetStoredProcedure
{ forall (b :: BackendType). GetStoredProcedure b -> SourceName
gspSource :: SourceName
}
deriving instance (Backend b) => Show (GetStoredProcedure b)
deriving instance (Backend b) => Eq (GetStoredProcedure b)
instance (Backend b) => FromJSON (GetStoredProcedure b) where
parseJSON :: Value -> Parser (GetStoredProcedure b)
parseJSON = String
-> (Object -> Parser (GetStoredProcedure b))
-> Value
-> Parser (GetStoredProcedure b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"GetStoredProcedure" ((Object -> Parser (GetStoredProcedure b))
-> Value -> Parser (GetStoredProcedure b))
-> (Object -> Parser (GetStoredProcedure b))
-> Value
-> Parser (GetStoredProcedure b)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
SourceName
gspSource <- Object
o Object -> Key -> Parser SourceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"source"
GetStoredProcedure b -> Parser (GetStoredProcedure b)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure GetStoredProcedure {SourceName
gspSource :: SourceName
gspSource :: SourceName
..}
instance (Backend b) => ToJSON (GetStoredProcedure b) where
toJSON :: GetStoredProcedure b -> Value
toJSON GetStoredProcedure {SourceName
gspSource :: forall (b :: BackendType). GetStoredProcedure b -> SourceName
gspSource :: SourceName
..} =
[Pair] -> Value
object
[ Key
"source" Key -> SourceName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SourceName
gspSource
]
runGetStoredProcedure ::
forall b m.
( BackendMetadata b,
MetadataM m
) =>
GetStoredProcedure b ->
m EncJSON
runGetStoredProcedure :: forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MetadataM m) =>
GetStoredProcedure b -> m EncJSON
runGetStoredProcedure GetStoredProcedure b
q = do
Metadata
metadata <- m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
let storedProcedure :: Maybe (StoredProcedures b)
storedProcedure :: Maybe (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
storedProcedure = Metadata
metadata Metadata
-> Getting
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Metadata
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
-> Maybe
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
forall s a. s -> Getting (First a) s a -> Maybe a
^? (Sources
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Sources)
-> Metadata
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Metadata
Lens' Metadata Sources
metaSources ((Sources
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Sources)
-> Metadata
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Metadata)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Sources
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Sources)
-> Getting
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Metadata
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix (GetStoredProcedure b -> SourceName
forall (b :: BackendType). GetStoredProcedure b -> SourceName
gspSource GetStoredProcedure b
q) ((BackendSourceMetadata
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
BackendSourceMetadata)
-> Sources
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Sources)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> BackendSourceMetadata
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
BackendSourceMetadata)
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Sources
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (SourceMetadata b
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(SourceMetadata b))
-> BackendSourceMetadata
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
BackendSourceMetadata
forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata ((SourceMetadata b
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(SourceMetadata b))
-> BackendSourceMetadata
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
BackendSourceMetadata)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> SourceMetadata b
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(SourceMetadata b))
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> BackendSourceMetadata
-> Const
(First
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType) (f :: * -> *).
Functor f =>
(StoredProcedures b -> f (StoredProcedures b))
-> SourceMetadata b -> f (SourceMetadata b)
smStoredProcedures @b
EncJSON -> m EncJSON
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe [StoredProcedureMetadata b] -> EncJSON
forall a. ToJSON a => a -> EncJSON
encJFromJValue (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> [StoredProcedureMetadata b]
forall k v. InsOrdHashMap k v -> [v]
InsOrdHashMap.elems (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> [StoredProcedureMetadata b])
-> Maybe
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
-> Maybe [StoredProcedureMetadata b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
storedProcedure))
runTrackStoredProcedure ::
forall b m.
( BackendMetadata b,
MonadError QErr m,
CacheRWM m,
MetadataM m
) =>
TrackStoredProcedure b ->
m EncJSON
runTrackStoredProcedure :: forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
TrackStoredProcedure b -> m EncJSON
runTrackStoredProcedure TrackStoredProcedure {Maybe Text
HashMap ArgumentName (NullableScalarType b)
SourceName
FunctionName b
LogicalModelName
StoredProcedureConfig
tspSource :: forall (b :: BackendType). TrackStoredProcedure b -> SourceName
tspStoredProcedure :: forall (b :: BackendType). TrackStoredProcedure b -> FunctionName b
tspConfig :: forall (b :: BackendType).
TrackStoredProcedure b -> StoredProcedureConfig
tspArguments :: forall (b :: BackendType).
TrackStoredProcedure b
-> HashMap ArgumentName (NullableScalarType b)
tspDescription :: forall (b :: BackendType). TrackStoredProcedure b -> Maybe Text
tspReturns :: forall (b :: BackendType).
TrackStoredProcedure b -> LogicalModelName
tspSource :: SourceName
tspStoredProcedure :: FunctionName b
tspConfig :: StoredProcedureConfig
tspArguments :: HashMap ArgumentName (NullableScalarType b)
tspDescription :: Maybe Text
tspReturns :: LogicalModelName
..} = do
SourceMetadata b
sourceMetadata <-
m (SourceMetadata b)
-> (SourceMetadata b -> m (SourceMetadata b))
-> Maybe (SourceMetadata b)
-> m (SourceMetadata b)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
( Code -> Text -> m (SourceMetadata b)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound
(Text -> m (SourceMetadata b)) -> Text -> m (SourceMetadata b)
forall a b. (a -> b) -> a -> b
$ Text
"Source '"
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName -> Text
sourceNameToText SourceName
tspSource
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' of kind "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> BackendType -> Text
forall a. ToTxt a => a -> Text
toTxt (BackendTag b -> BackendType
forall (b :: BackendType). BackendTag b -> BackendType
reify (forall (b :: BackendType). HasTag b => BackendTag b
backendTag @b))
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" not found."
)
SourceMetadata b -> m (SourceMetadata b)
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Maybe (SourceMetadata b) -> m (SourceMetadata b))
-> (Metadata -> Maybe (SourceMetadata b))
-> Metadata
-> m (SourceMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
-> Metadata -> Maybe (SourceMetadata b)
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview ((Sources -> Const (First (SourceMetadata b)) Sources)
-> Metadata -> Const (First (SourceMetadata b)) Metadata
Lens' Metadata Sources
metaSources ((Sources -> Const (First (SourceMetadata b)) Sources)
-> Metadata -> Const (First (SourceMetadata b)) Metadata)
-> ((SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> Sources -> Const (First (SourceMetadata b)) Sources)
-> Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
tspSource ((BackendSourceMetadata
-> Const (First (SourceMetadata b)) BackendSourceMetadata)
-> Sources -> Const (First (SourceMetadata b)) Sources)
-> ((SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> BackendSourceMetadata
-> Const (First (SourceMetadata b)) BackendSourceMetadata)
-> (SourceMetadata b
-> Const (First (SourceMetadata b)) (SourceMetadata b))
-> Sources
-> Const (First (SourceMetadata b)) Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b)
(Metadata -> m (SourceMetadata b))
-> m Metadata -> m (SourceMetadata b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
let metadata :: StoredProcedureMetadata b
metadata =
StoredProcedureMetadata
{ _spmStoredProcedure :: FunctionName b
_spmStoredProcedure = FunctionName b
tspStoredProcedure,
_spmConfig :: StoredProcedureConfig
_spmConfig = StoredProcedureConfig
tspConfig,
_spmReturns :: LogicalModelName
_spmReturns = LogicalModelName
tspReturns,
_spmArguments :: HashMap ArgumentName (NullableScalarType b)
_spmArguments = HashMap ArgumentName (NullableScalarType b)
tspArguments,
_spmDescription :: Maybe Text
_spmDescription = Maybe Text
tspDescription
}
let storedProcedure :: FunctionName b
storedProcedure = StoredProcedureMetadata b -> FunctionName b
forall (b :: BackendType).
StoredProcedureMetadata b -> FunctionName b
_spmStoredProcedure StoredProcedureMetadata b
metadata
metadataObj :: MetadataObjId
metadataObj =
SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
tspSource
(AnyBackend SourceMetadataObjId -> MetadataObjId)
-> AnyBackend SourceMetadataObjId -> MetadataObjId
forall a b. (a -> b) -> a -> b
$ SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend
(SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). FunctionName b -> SourceMetadataObjId b
SMOStoredProcedure @b FunctionName b
storedProcedure
existingStoredProcedures :: [FunctionName b]
existingStoredProcedures = InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> [FunctionName b]
forall k v. InsOrdHashMap k v -> [k]
InsOrdHashMap.keys (SourceMetadata b
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
forall (b :: BackendType). SourceMetadata b -> StoredProcedures b
_smStoredProcedures SourceMetadata b
sourceMetadata)
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (FunctionName b
storedProcedure FunctionName b -> [FunctionName b] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [FunctionName b]
existingStoredProcedures) do
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
AlreadyTracked (Text -> m ()) -> Text -> m ()
forall a b. (a -> b) -> a -> b
$ Text
"Stored procedure '" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FunctionName b -> Text
forall a. ToTxt a => a -> Text
toTxt FunctionName b
storedProcedure Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"' is already tracked."
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor MetadataObjId
metadataObj
(MetadataModifier -> m ()) -> MetadataModifier -> m ()
forall a b. (a -> b) -> a -> b
$ (Metadata -> Metadata) -> MetadataModifier
MetadataModifier
((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ ((Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources ((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Sources -> Identity Sources)
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
tspSource ((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b ((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(StoredProcedures b -> f (StoredProcedures b))
-> SourceMetadata b -> f (SourceMetadata b)
smStoredProcedures)
((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Metadata -> Identity Metadata)
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ FunctionName b
-> StoredProcedureMetadata b
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
forall k v.
(Eq k, Hashable k) =>
k -> v -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.insert FunctionName b
storedProcedure StoredProcedureMetadata b
metadata
EncJSON -> m EncJSON
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg
data UntrackStoredProcedure (b :: BackendType) = UntrackStoredProcedure
{ forall (b :: BackendType). UntrackStoredProcedure b -> SourceName
utspSource :: SourceName,
forall (b :: BackendType).
UntrackStoredProcedure b -> FunctionName b
utspStoredProcedure :: FunctionName b
}
deriving instance (Backend b) => Show (UntrackStoredProcedure b)
deriving instance (Backend b) => Eq (UntrackStoredProcedure b)
instance (Backend b) => FromJSON (UntrackStoredProcedure b) where
parseJSON :: Value -> Parser (UntrackStoredProcedure b)
parseJSON = String
-> (Object -> Parser (UntrackStoredProcedure b))
-> Value
-> Parser (UntrackStoredProcedure b)
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"UntrackStoredProcedure" ((Object -> Parser (UntrackStoredProcedure b))
-> Value -> Parser (UntrackStoredProcedure b))
-> (Object -> Parser (UntrackStoredProcedure b))
-> Value
-> Parser (UntrackStoredProcedure b)
forall a b. (a -> b) -> a -> b
$ \Object
o -> do
SourceName
utspSource <- Object
o Object -> Key -> Parser SourceName
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"source"
FunctionName b
utspStoredProcedure <- Object
o Object -> Key -> Parser (FunctionName b)
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"stored_procedure"
UntrackStoredProcedure b -> Parser (UntrackStoredProcedure b)
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure UntrackStoredProcedure {SourceName
FunctionName b
utspSource :: SourceName
utspStoredProcedure :: FunctionName b
utspSource :: SourceName
utspStoredProcedure :: FunctionName b
..}
instance (Backend b) => ToJSON (UntrackStoredProcedure b) where
toJSON :: UntrackStoredProcedure b -> Value
toJSON UntrackStoredProcedure {SourceName
FunctionName b
utspSource :: forall (b :: BackendType). UntrackStoredProcedure b -> SourceName
utspStoredProcedure :: forall (b :: BackendType).
UntrackStoredProcedure b -> FunctionName b
utspSource :: SourceName
utspStoredProcedure :: FunctionName b
..} =
[Pair] -> Value
object
[ Key
"source" Key -> SourceName -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= SourceName
utspSource,
Key
"stored_procedure" Key -> FunctionName b -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= FunctionName b
utspStoredProcedure
]
runUntrackStoredProcedure ::
forall b m.
( BackendMetadata b,
MonadError QErr m,
CacheRWM m,
MetadataM m
) =>
UntrackStoredProcedure b ->
m EncJSON
runUntrackStoredProcedure :: forall (b :: BackendType) (m :: * -> *).
(BackendMetadata b, MonadError QErr m, CacheRWM m, MetadataM m) =>
UntrackStoredProcedure b -> m EncJSON
runUntrackStoredProcedure UntrackStoredProcedure b
q = do
forall (b :: BackendType) (m :: * -> *).
(Backend b, MetadataM m, MonadError QErr m) =>
SourceName -> FunctionName b -> m ()
assertStoredProcedureExists @b SourceName
source FunctionName b
storedProcedure
let metadataObj :: MetadataObjId
metadataObj =
SourceName -> AnyBackend SourceMetadataObjId -> MetadataObjId
MOSourceObjId SourceName
source
(AnyBackend SourceMetadataObjId -> MetadataObjId)
-> AnyBackend SourceMetadataObjId -> MetadataObjId
forall a b. (a -> b) -> a -> b
$ SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall (b :: BackendType) (i :: BackendType -> *).
HasTag b =>
i b -> AnyBackend i
AB.mkAnyBackend
(SourceMetadataObjId b -> AnyBackend SourceMetadataObjId)
-> SourceMetadataObjId b -> AnyBackend SourceMetadataObjId
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType). FunctionName b -> SourceMetadataObjId b
SMOStoredProcedure @b FunctionName b
storedProcedure
MetadataObjId -> MetadataModifier -> m ()
forall (m :: * -> *).
(QErrM m, CacheRWM m, MetadataM m) =>
MetadataObjId -> MetadataModifier -> m ()
buildSchemaCacheFor MetadataObjId
metadataObj
(MetadataModifier -> m ()) -> MetadataModifier -> m ()
forall a b. (a -> b) -> a -> b
$ forall (b :: BackendType).
BackendMetadata b =>
SourceName -> FunctionName b -> MetadataModifier
dropStoredProcedureInMetadata @b SourceName
source FunctionName b
storedProcedure
EncJSON -> m EncJSON
forall a. a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure EncJSON
successMsg
where
source :: SourceName
source = UntrackStoredProcedure b -> SourceName
forall (b :: BackendType). UntrackStoredProcedure b -> SourceName
utspSource UntrackStoredProcedure b
q
storedProcedure :: FunctionName b
storedProcedure = UntrackStoredProcedure b -> FunctionName b
forall (b :: BackendType).
UntrackStoredProcedure b -> FunctionName b
utspStoredProcedure UntrackStoredProcedure b
q
dropStoredProcedureInMetadata ::
forall b.
(BackendMetadata b) =>
SourceName ->
FunctionName b ->
MetadataModifier
dropStoredProcedureInMetadata :: forall (b :: BackendType).
BackendMetadata b =>
SourceName -> FunctionName b -> MetadataModifier
dropStoredProcedureInMetadata SourceName
source FunctionName b
rootFieldName = do
(Metadata -> Metadata) -> MetadataModifier
MetadataModifier
((Metadata -> Metadata) -> MetadataModifier)
-> (Metadata -> Metadata) -> MetadataModifier
forall a b. (a -> b) -> a -> b
$ (Sources -> Identity Sources) -> Metadata -> Identity Metadata
Lens' Metadata Sources
metaSources
((Sources -> Identity Sources) -> Metadata -> Identity Metadata)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Sources -> Identity Sources)
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Metadata
-> Identity Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
source
((BackendSourceMetadata -> Identity BackendSourceMetadata)
-> Sources -> Identity Sources)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Sources
-> Identity Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b
((SourceMetadata b -> Identity (SourceMetadata b))
-> BackendSourceMetadata -> Identity BackendSourceMetadata)
-> ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b))
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> BackendSourceMetadata
-> Identity BackendSourceMetadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> SourceMetadata b -> Identity (SourceMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(StoredProcedures b -> f (StoredProcedures b))
-> SourceMetadata b -> f (SourceMetadata b)
smStoredProcedures
((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> Identity
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> Metadata -> Identity Metadata)
-> (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
-> Metadata
-> Metadata
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ FunctionName b
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
forall k v.
(Eq k, Hashable k) =>
k -> InsOrdHashMap k v -> InsOrdHashMap k v
InsOrdHashMap.delete FunctionName b
rootFieldName
assertStoredProcedureExists ::
forall b m.
(Backend b, MetadataM m, MonadError QErr m) =>
SourceName ->
FunctionName b ->
m ()
assertStoredProcedureExists :: forall (b :: BackendType) (m :: * -> *).
(Backend b, MetadataM m, MonadError QErr m) =>
SourceName -> FunctionName b -> m ()
assertStoredProcedureExists SourceName
sourceName FunctionName b
storedProcedure = do
Metadata
metadata <- m Metadata
forall (m :: * -> *). MetadataM m => m Metadata
getMetadata
let sourceMetadataTraversal :: Traversal' Metadata (SourceMetadata b)
sourceMetadataTraversal :: Traversal' Metadata (SourceMetadata b)
sourceMetadataTraversal = (Sources -> f Sources) -> Metadata -> f Metadata
Lens' Metadata Sources
metaSources ((Sources -> f Sources) -> Metadata -> f Metadata)
-> ((SourceMetadata b -> f (SourceMetadata b))
-> Sources -> f Sources)
-> (SourceMetadata b -> f (SourceMetadata b))
-> Metadata
-> f Metadata
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index Sources -> Traversal' Sources (IxValue Sources)
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index Sources
SourceName
sourceName ((BackendSourceMetadata -> f BackendSourceMetadata)
-> Sources -> f Sources)
-> ((SourceMetadata b -> f (SourceMetadata b))
-> BackendSourceMetadata -> f BackendSourceMetadata)
-> (SourceMetadata b -> f (SourceMetadata b))
-> Sources
-> f Sources
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (b :: BackendType).
Backend b =>
Prism' BackendSourceMetadata (SourceMetadata b)
toSourceMetadata @b
SourceMetadata b
sourceMetadata <-
Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
-> Metadata -> Maybe (SourceMetadata b)
forall s (m :: * -> *) a.
MonadReader s m =>
Getting (First a) s a -> m (Maybe a)
preview Getting (First (SourceMetadata b)) Metadata (SourceMetadata b)
Traversal' Metadata (SourceMetadata b)
sourceMetadataTraversal Metadata
metadata
Maybe (SourceMetadata b)
-> m (SourceMetadata b) -> m (SourceMetadata b)
forall (m :: * -> *) a. Applicative m => Maybe a -> m a -> m a
`onNothing` Code -> Text -> m (SourceMetadata b)
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound (Text
"Source " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
sourceName SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" not found.")
let desiredStoredProcedure :: Traversal' (SourceMetadata b) (StoredProcedureMetadata b)
desiredStoredProcedure :: Traversal' (SourceMetadata b) (StoredProcedureMetadata b)
desiredStoredProcedure = (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> f (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> SourceMetadata b -> f (SourceMetadata b)
forall (b :: BackendType) (f :: * -> *).
Functor f =>
(StoredProcedures b -> f (StoredProcedures b))
-> SourceMetadata b -> f (SourceMetadata b)
smStoredProcedures ((InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> f (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> SourceMetadata b -> f (SourceMetadata b))
-> ((StoredProcedureMetadata b -> f (StoredProcedureMetadata b))
-> InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)
-> f (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
-> (StoredProcedureMetadata b -> f (StoredProcedureMetadata b))
-> SourceMetadata b
-> f (SourceMetadata b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Index (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
-> Traversal'
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
(IxValue
(InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b)))
forall m. Ixed m => Index m -> Traversal' m (IxValue m)
ix Index (InsOrdHashMap (FunctionName b) (StoredProcedureMetadata b))
FunctionName b
storedProcedure
Bool -> m () -> m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (Getting Any (SourceMetadata b) (StoredProcedureMetadata b)
-> SourceMetadata b -> Bool
forall s a. Getting Any s a -> s -> Bool
has Getting Any (SourceMetadata b) (StoredProcedureMetadata b)
Traversal' (SourceMetadata b) (StoredProcedureMetadata b)
desiredStoredProcedure SourceMetadata b
sourceMetadata) do
Code -> Text -> m ()
forall (m :: * -> *) a. QErrM m => Code -> Text -> m a
throw400 Code
NotFound (Text
"Stored Procedure " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> FunctionName b -> Text
forall a. ToTxt a => a -> Text
toTxt FunctionName b
storedProcedure Text -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
" not found in source " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SourceName
sourceName SourceName -> Text -> Text
forall t. ToTxt t => t -> Text -> Text
<<> Text
".")