graphql-engine/server/src-lib/Hasura/Backends/DataConnector/IR/Name.hs
Samir Talwar eab4f75212 An ErrorMessage type, to encapsulate.
This introduces an `ErrorMessage` newtype which wraps `Text` in a manner which is designed to be easy to construct, and difficult to deconstruct.

It provides functionality similar to `Data.Text.Extended`, but designed _only_ for error messages. Error messages are constructed through `fromString`, concatenation, or the `toErrorValue` function, which is designed to be overridden for all meaningful domain types that might show up in an error message. Notably, there are not and should never be instances of `ToErrorValue` for `String`, `Text`, `Int`, etc. This is so that we correctly represent the value in a way that is specific to its type. For example, all `Name` values (from the _graphql-parser-hs_ library) are single-quoted now; no exceptions.

I have mostly had to add `instance ToErrorValue` for various backend types (and also add newtypes where necessary). Some of these are not strictly necessary for this changeset, as I had bigger aspirations when I started. These aspirations have been tempered by trying and failing twice.

As such, in this changeset, I have started by introducing this type to the `parseError` and `parseErrorWith` functions. In the future, I would like to extend this to the `QErr` record and the various `throwError` functions, but this is a much larger task and should probably be done in stages.

For now, `toErrorMessage` and `fromErrorMessage` are provided for conversion to and from `Text`, but the intent is to stop exporting these once all error messages are converted to the new type.

PR-URL: https://github.com/hasura/graphql-engine-mono/pull/5018
GitOrigin-RevId: 84b37e238992e4312255a87ca44f41af65e2d89a
2022-07-18 20:27:06 +00:00

74 lines
2.1 KiB
Haskell

{-# LANGUAGE StandaloneKindSignatures #-}
module Hasura.Backends.DataConnector.IR.Name
( Name (..),
NameType (..),
)
where
--------------------------------------------------------------------------------
import Data.Aeson (FromJSON, FromJSONKey, ToJSON, ToJSONKey)
import Data.Kind (Type)
import Data.Text.Extended (ToTxt)
import Hasura.Backends.DataConnector.API qualified as API
import Hasura.Base.ErrorValue qualified as ErrorValue
import Hasura.Base.ToErrorValue
import Hasura.Incremental (Cacheable)
import Hasura.Prelude
import Witch qualified
--------------------------------------------------------------------------------
-- | A tagged, opaque wrapper around 'Text' that provides a number of derived
-- derived instances (primarily as required by the @Backend@ typeclass).
--
-- This wrapper is indexed by 'NameType' so that different "names" can be
-- represented as semantically distinct types without the boilerplate of
-- actually defining these wrappers separately.
type Name :: NameType -> Type
newtype Name ty = Name {unName :: Text}
deriving stock (Data, Eq, Generic, Ord, Show)
deriving newtype
( Cacheable,
FromJSON,
FromJSONKey,
Hashable,
NFData,
ToJSON,
ToJSONKey,
ToTxt
)
instance ToErrorValue (Name ty) where
toErrorValue = ErrorValue.squote . unName
instance Witch.From API.TableName (Name 'Table) where
from (API.TableName n) = Name n
instance Witch.From (Name 'Table) API.TableName where
from (Name n) = API.TableName n
instance Witch.From API.ColumnName (Name 'Column) where
from (API.ColumnName n) = Name n
instance Witch.From (Name 'Column) API.ColumnName where
from (Name n) = API.ColumnName n
instance Witch.From API.RelationshipName (Name 'Relationship) where
from (API.RelationshipName n) = Name n
instance Witch.From (Name 'Relationship) API.RelationshipName where
from (Name n) = API.RelationshipName n
-- | The "type" of "name" that the 'Name' type is meant to provide a textual
-- representation for.
--
-- In other words: an enumeration of all the types for which 'Name' acts as a
-- shared abstraction.
data NameType
= Column
| Function
| Table
| Relationship