2023-04-27 17:02:55 +03:00
|
|
|
{-# LANGUAGE DeriveAnyClass #-}
|
|
|
|
{-# LANGUAGE TemplateHaskell #-}
|
|
|
|
{-# LANGUAGE UndecidableInstances #-}
|
|
|
|
|
|
|
|
-- | Metadata representation of a stored procedure in the metadata,
|
|
|
|
-- as well as a parser and prettyprinter for the query code.
|
|
|
|
module Hasura.StoredProcedure.Metadata
|
2023-05-02 16:30:22 +03:00
|
|
|
( StoredProcedureMetadata (..),
|
|
|
|
spmStoredProcedure,
|
|
|
|
spmConfig,
|
2023-04-27 17:02:55 +03:00
|
|
|
spmArguments,
|
|
|
|
spmDescription,
|
|
|
|
spmReturns,
|
2023-05-02 15:54:30 +03:00
|
|
|
ArgumentName (..),
|
2023-04-27 17:02:55 +03:00
|
|
|
module Hasura.StoredProcedure.Types,
|
|
|
|
)
|
|
|
|
where
|
|
|
|
|
|
|
|
import Autodocodec
|
|
|
|
import Autodocodec qualified as AC
|
|
|
|
import Control.Lens (makeLenses)
|
2023-04-28 22:23:32 +03:00
|
|
|
import Data.Aeson (FromJSON, ToJSON)
|
2023-04-27 17:02:55 +03:00
|
|
|
import Hasura.LogicalModel.Types
|
2023-05-03 12:59:21 +03:00
|
|
|
import Hasura.LogicalModelResolver.Types (ArgumentName (..))
|
2023-04-27 17:02:55 +03:00
|
|
|
import Hasura.Prelude hiding (first)
|
|
|
|
import Hasura.RQL.Types.Backend
|
|
|
|
import Hasura.RQL.Types.BackendTag (backendPrefix)
|
|
|
|
import Hasura.RQL.Types.BackendType
|
2023-05-02 16:30:22 +03:00
|
|
|
import Hasura.StoredProcedure.Types (NullableScalarType (..), StoredProcedureConfig (..), nullableScalarTypeMapCodec)
|
2023-04-27 17:02:55 +03:00
|
|
|
|
|
|
|
---------------------------------------
|
|
|
|
|
2023-05-03 12:59:21 +03:00
|
|
|
-- | The representation of stored procedures within the metadata structure.
|
2023-04-27 17:02:55 +03:00
|
|
|
data StoredProcedureMetadata (b :: BackendType) = StoredProcedureMetadata
|
2023-05-02 16:30:22 +03:00
|
|
|
{ _spmStoredProcedure :: FunctionName b,
|
|
|
|
_spmConfig :: StoredProcedureConfig,
|
2023-04-27 17:02:55 +03:00
|
|
|
_spmReturns :: LogicalModelName,
|
2023-05-02 15:54:30 +03:00
|
|
|
_spmArguments :: HashMap ArgumentName (NullableScalarType b),
|
2023-04-27 17:02:55 +03:00
|
|
|
_spmDescription :: Maybe Text
|
|
|
|
}
|
|
|
|
deriving (Generic)
|
|
|
|
|
2023-05-24 16:51:56 +03:00
|
|
|
deriving instance (Backend b) => Eq (StoredProcedureMetadata b)
|
2023-04-27 17:02:55 +03:00
|
|
|
|
2023-05-24 16:51:56 +03:00
|
|
|
deriving instance (Backend b) => Show (StoredProcedureMetadata b)
|
2023-04-27 17:02:55 +03:00
|
|
|
|
|
|
|
instance (Backend b) => HasCodec (StoredProcedureMetadata b) where
|
|
|
|
codec =
|
|
|
|
CommentCodec
|
|
|
|
("A stored procedure as represented in metadata.")
|
|
|
|
$ AC.object (backendPrefix @b <> "StoredProcedureMetadata")
|
|
|
|
$ StoredProcedureMetadata
|
2023-05-24 16:51:56 +03:00
|
|
|
<$> AC.requiredField "stored_procedure" spDoc
|
|
|
|
AC..= _spmStoredProcedure
|
2023-05-02 16:30:22 +03:00
|
|
|
<*> requiredField "configuration" configDoc
|
2023-05-24 16:51:56 +03:00
|
|
|
AC..= _spmConfig
|
2023-04-27 17:02:55 +03:00
|
|
|
<*> requiredField "returns" returnsDoc
|
2023-05-24 16:51:56 +03:00
|
|
|
AC..= _spmReturns
|
2023-04-27 17:02:55 +03:00
|
|
|
<*> optionalFieldWithDefault "arguments" mempty argumentDoc
|
2023-05-24 16:51:56 +03:00
|
|
|
AC..= _spmArguments
|
2023-04-27 17:02:55 +03:00
|
|
|
<*> optionalField "description" descriptionDoc
|
2023-05-24 16:51:56 +03:00
|
|
|
AC..= _spmDescription
|
2023-04-27 17:02:55 +03:00
|
|
|
where
|
2023-05-02 16:30:22 +03:00
|
|
|
spDoc = "The name of the SQL stored procedure"
|
|
|
|
configDoc = "The configuration for the SQL stored procedure"
|
2023-04-27 17:02:55 +03:00
|
|
|
argumentDoc = "Free variables in the expression and their types"
|
|
|
|
returnsDoc = "Return type (table) of the expression"
|
|
|
|
descriptionDoc = "A description of the stored procedure which appears in the graphql schema"
|
|
|
|
|
|
|
|
deriving via
|
|
|
|
(Autodocodec (StoredProcedureMetadata b))
|
|
|
|
instance
|
|
|
|
(Backend b) => (FromJSON (StoredProcedureMetadata b))
|
|
|
|
|
|
|
|
deriving via
|
|
|
|
(Autodocodec (StoredProcedureMetadata b))
|
|
|
|
instance
|
|
|
|
(Backend b) => (ToJSON (StoredProcedureMetadata b))
|
|
|
|
|
|
|
|
makeLenses ''StoredProcedureMetadata
|